Skip to navigation


Elite J source

[Commodore 64 version]

ELITE J FILE Produces the binary file ELTJ.bin that gets loaded by elite-checksum.py.
CODE_J% = P% LOAD_J% = LOAD% + P% - CODE%
Name: STARTUP [Show more] Type: Subroutine Category: Loader Summary: Set the various vectors, interrupts and timers
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine is unused in this version of Elite (it is left over from the 6502 Second Processor version).
.STARTUP LDA #$FF ; Set COL to $FF, which would set the colour to green STA COL ; for a dashboard indicator (though this code is never ; run) ; Fall through into PUTBACK to return from the ; subroutine
Name: PUTBACK [Show more] Type: Subroutine Category: Tube Summary: Reset the OSWRCH vector in WRCHV to point to USOSWRCH
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine is unused in this version of Elite (it is left over from the 6502 Second Processor version).
.PUTBACK ;LDA #128 ; This instruction is commented out in the original ; source RTS ; Return from the subroutine
Name: DOHFX [Show more] Type: Subroutine Category: Drawing circles Summary: Implement the #DOHFX <flag> command (update the hyperspace effect flag)
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine is unused in this version of Elite (it is left over from the 6502 Second Processor version).
.DOHFX ;STA HFX ; These instructions are commented out in the original ;JMP PUTBACK ; source
Name: DOCOL [Show more] Type: Subroutine Category: Text Summary: Implement the #SETCOL <colour> command (set the current colour)
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine is unused in this version of Elite (it is left over from the 6502 Second Processor version).
.DOCOL STA COL ; Store the new colour in COL RTS ; Return from the subroutine
Name: DOSVN [Show more] Type: Subroutine Category: Save and load Summary: Implement the #DOSVN <flag> command (update the "save in progress" flag)
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine is unused in this version of Elite (it is left over from the 6502 Second Processor version).
.DOSVN ;STA svn ; These instructions are commented out in the original ;JMP PUTBACK ; source
Name: TWOS [Show more] Type: Variable Category: Drawing pixels Summary: Ready-made single-pixel character row bytes for mode 4 Deep dive: Drawing monochrome pixels in mode 4
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 5 of 7) uses TWOS

Ready-made bytes for plotting one-pixel points the space view. See the PIXEL routine for details.
.TWOS EQUB %10000000 EQUB %01000000 EQUB %00100000 EQUB %00010000 EQUB %00001000 EQUB %00000100 EQUB %00000010 EQUB %00000001 EQUB %10000000 EQUB %01000000
Name: DTWOS [Show more] Type: Variable Category: Drawing pixels Summary: An unused table of ready-made double-pixel character row bytes for the dashboard
Context: See this variable on its own page References: No direct references to this variable in this source file
.DTWOS EQUB %11000000 EQUB %00110000 EQUB %00001100 EQUB %00000011 EQUD $3060C0C0 ; These bytes appear to be unused; they contain a copy EQUD $03060C18 ; of the TWOS2 variable, and the original source has a ; commented out label .TWOS2
Name: CTWOS2 [Show more] Type: Variable Category: Drawing pixels Summary: Ready-made single-pixel character row bytes for multicolour bitmap mode
Context: See this variable on its own page References: This variable is used as follows: * CPIX2 uses CTWOS2 * SCAN uses CTWOS2
.CTWOS2 EQUB %11000000 EQUB %11000000 EQUB %00110000 EQUB %00110000 EQUB %00001100 EQUB %00001100 EQUB %00000011 EQUB %00000011 EQUB %11000000 EQUB %11000000
Name: LIJT1 [Show more] Type: Variable Category: Drawing lines Summary: Addresses for modifying the low byte of the JMP instruction at LI71 to support the unrolled algorithm in part 3 of LOIN
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 3 of 7) uses LIJT1
.LIJT1 EQUB LO(LI81) EQUB LO(LI82) EQUB LO(LI83) EQUB LO(LI84) EQUB LO(LI85) EQUB LO(LI86) EQUB LO(LI87) EQUB LO(LI88)
Name: LIJT2 [Show more] Type: Variable Category: Drawing lines Summary: Addresses for modifying the high byte of the JMP instruction at LI71 to support the unrolled algorithm in part 3 of LOIN
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 3 of 7) uses LIJT2
.LIJT2 EQUB HI(LI81) EQUB HI(LI82) EQUB HI(LI83) EQUB HI(LI84) EQUB HI(LI85) EQUB HI(LI86) EQUB HI(LI87) EQUB HI(LI88)
Name: LIJT3 [Show more] Type: Variable Category: Drawing lines Summary: Addresses for modifying the low byte of the JMP instruction at LI72 to support the unrolled algorithm in part 3 of LOIN
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 3 of 7) uses LIJT3
.LIJT3 EQUB LO(LI81+6) EQUB LO(LI82+6) EQUB LO(LI83+6) EQUB LO(LI84+6) EQUB LO(LI85+6) EQUB LO(LI86+6) EQUB LO(LI87+6) EQUB LO(LI88+6)
Name: LIJT4 [Show more] Type: Variable Category: Drawing lines Summary: Addresses for modifying the high byte of the JMP instruction at LI72 to support the unrolled algorithm in part 3 of LOIN
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 3 of 7) uses LIJT4
.LIJT4 EQUB HI(LI81+6) EQUB HI(LI82+6) EQUB HI(LI83+6) EQUB HI(LI84+6) EQUB HI(LI85+6) EQUB HI(LI86+6) EQUB HI(LI87+6) EQUB HI(LI88+6)
Name: LIJT5 [Show more] Type: Variable Category: Drawing lines Summary: Addresses for modifying the low byte of the JMP instruction at LI91 to support the unrolled algorithm in part 4 of LOIN
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 4 of 7) uses LIJT5
.LIJT5 EQUB LO(LI21) EQUB LO(LI22) EQUB LO(LI23) EQUB LO(LI24) EQUB LO(LI25) EQUB LO(LI26) EQUB LO(LI27) EQUB LO(LI28)
Name: LIJT6 [Show more] Type: Variable Category: Drawing lines Summary: Addresses for modifying the high byte of the JMP instruction at LI91 to support the unrolled algorithm in part 4 of LOIN
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 4 of 7) uses LIJT6
.LIJT6 EQUB HI(LI21) EQUB HI(LI22) EQUB HI(LI23) EQUB HI(LI24) EQUB HI(LI25) EQUB HI(LI26) EQUB HI(LI27) EQUB HI(LI28)
Name: LIJT7 [Show more] Type: Variable Category: Drawing lines Summary: Addresses for modifying the low byte of the JMP instruction at LI92 to support the unrolled algorithm in part 4 of LOIN
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 4 of 7) uses LIJT7
.LIJT7 EQUB LO(LI21+6) EQUB LO(LI22+6) EQUB LO(LI23+6) EQUB LO(LI24+6) EQUB LO(LI25+6) EQUB LO(LI26+6) EQUB LO(LI27+6) EQUB LO(LI28+6)
Name: LIJT8 [Show more] Type: Variable Category: Drawing lines Summary: Addresses for modifying the high byte of the JMP instruction at LI92 to support the unrolled algorithm in part 4 of LOIN
Context: See this variable on its own page References: This variable is used as follows: * LOIN (Part 4 of 7) uses LIJT8
.LIJT8 EQUB HI(LI21+6) EQUB HI(LI22+6) EQUB HI(LI23+6) EQUB HI(LI24+6) EQUB HI(LI25+6) EQUB HI(LI26+6) EQUB HI(LI27+6) EQUB HI(LI28+6)
Name: LOIN (Part 1 of 7) [Show more] Type: Subroutine Category: Drawing lines Summary: Draw a line: Calculate the line gradient in the form of deltas Deep dive: Bresenham's line algorithm
Context: See this subroutine on its own page References: This subroutine is called as follows: * BLINE calls LOIN * WPLS2 calls LOIN * LASLI calls via LL30 * LL9 (Part 12 of 12) calls via LL30 * NLIN2 calls via LL30 * TT15 calls via LL30

This routine draws a line from (X1, Y1) to (X2, Y2). It has multiple stages. This stage calculates the line deltas.
Arguments: X1 The screen x-coordinate of the start of the line Y1 The screen y-coordinate of the start of the line X2 The screen x-coordinate of the end of the line Y2 The screen y-coordinate of the end of the line
Returns: Y Y is preserved
Other entry points: LL30 LL30 is a synonym for LOIN and draws a line from (X1, Y1) to (X2, Y2)
.LL30 SKIP 0 ; LL30 is a synonym for LOIN ; ; In the BBC Micro cassette and disc versions of Elite, ; LL30 and LOIN are synonyms for the same routine, ; presumably because the two developers each had their ; own line routines to start with, and then chose one of ; them for the final game .LOIN STY YSAV ; Store Y into YSAV, so we can preserve it across the ; call to this subroutine LDA #128 ; Set S2 = 128, which is the starting point for the STA S2 ; slope error (representing half a pixel) ASL A ; Set SWAP = 0, as %10000000 << 1 = 0 STA SWAP LDA X2 ; Set A = X2 - X1 SBC X1 ; = delta_x ; ; This subtraction works as the ASL A above sets the C ; flag BCS LI1 ; If X2 > X1 then A is already positive and we can skip ; the next three instructions EOR #%11111111 ; Negate the result in A by flipping all the bits and ADC #1 ; adding 1, i.e. using two's complement to make it ; positive .LI1 STA P2 ; Store A in P2, so P2 = |X2 - X1|, or |delta_x| SEC ; Set the C flag, ready for the subtraction below LDA Y2 ; Set A = Y2 - Y1 SBC Y1 ; = delta_y ; ; This subtraction works as we either set the C flag ; above, or we skipped that SEC instruction with a BCS BCS LI2 ; If Y2 > Y1 then A is already positive and we can skip ; the next two instructions EOR #%11111111 ; Negate the result in A by flipping all the bits and ADC #1 ; adding 1, i.e. using two's complement to make it ; positive .LI2 STA Q2 ; Store A in Q2, so Q2 = |Y2 - Y1|, or |delta_y| CMP P2 ; If Q2 < P2, jump to STPX to step along the x-axis, as BCC STPX ; the line is closer to being horizontal than vertical JMP STPY ; Otherwise Q2 >= P2 so jump to STPY to step along the ; y-axis, as the line is closer to being vertical than ; horizontal
Name: LOIN (Part 2 of 7) [Show more] Type: Subroutine Category: Drawing lines Summary: Draw a line: Line has a shallow gradient, step right along x-axis Deep dive: Bresenham's line algorithm
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine draws a line from (X1, Y1) to (X2, Y2). It has multiple stages. If we get here, then: * |delta_y| < |delta_x| * The line is closer to being horizontal than vertical * We are going to step right along the x-axis * We potentially swap coordinates to make sure X1 < X2
.STPX LDX X1 ; Set X = X1 CPX X2 ; If X1 < X2, jump down to LI3, as the coordinates are BCC LI3 ; already in the order that we want DEC SWAP ; Otherwise decrement SWAP from 0 to $FF, to denote that ; we are swapping the coordinates around LDA X2 ; Swap the values of X1 and X2 STA X1 STX X2 TAX ; Set X = X1 LDA Y2 ; Swap the values of Y1 and Y2 LDY Y1 STA Y1 STY Y2 .LI3 ; By this point we know the line is horizontal-ish and ; X1 < X2, so we're going from left to right as we go ; from X1 to X2 ; The following section calculates: ; ; Q2 = Q2 / P2 ; = |delta_y| / |delta_x| ; ; using the log tables at logL and log to calculate: ; ; A = log(Q2) - log(P2) ; = log(|delta_y|) - log(|delta_x|) ; ; by first subtracting the low bytes of the logarithms ; from the table at LogL, and then subtracting the high ; bytes from the table at log, before applying the ; antilog to get the result of the division and putting ; it in Q2 LDX Q2 ; Set X = |delta_y| BEQ LIlog7 ; If |delta_y| = 0, jump to LIlog7 to return 0 as the ; result of the division LDA logL,X ; Set A = log(Q2) - log(P2) LDX P2 ; = log(|delta_y|) - log(|delta_x|) SEC ; SBC logL,X ; by first subtracting the low bytes of ; log(Q2) - log(P2) BMI LIlog4 ; If A > 127, jump to LIlog4 LDX Q2 ; And then subtracting the high bytes of LDA log,X ; log(Q2) - log(P2) so now A contains the high byte of LDX P2 ; log(Q2) - log(P2) SBC log,X BCS LIlog5 ; If the subtraction fitted into one byte and didn't ; underflow, then log(Q2) - log(P2) < 256, so we jump to ; LIlog5 to return a result of 255 TAX ; Otherwise we set A to the A-th entry from the antilog LDA antilog,X ; table so the result of the division is now in A JMP LIlog6 ; Jump to LIlog6 to return the result .LIlog5 LDA #255 ; The division is very close to 1, so set A to the BNE LIlog6 ; closest possible answer to 256, i.e. 255, and jump to ; LIlog6 to return the result (this BNE is effectively a ; JMP as A is never zero) .LIlog7 LDA #0 ; The numerator in the division is 0, so set A to 0 and BEQ LIlog6 ; jump to LIlog6 to return the result (this BEQ is ; effectively a JMP as A is always zero) .LIlog4 LDX Q2 ; Subtract the high bytes of log(Q2) - log(P2) so now A LDA log,X ; contains the high byte of log(Q2) - log(P2) LDX P2 SBC log,X BCS LIlog5 ; If the subtraction fitted into one byte and didn't ; underflow, then log(Q2) - log(P2) < 256, so we jump to ; LIlog5 to return a result of 255 TAX ; Otherwise we set A to the A-th entry from the LDA antilogODD,X ; antilogODD so the result of the division is now in A .LIlog6 STA Q2 ; Store the result of the division in Q2, so we have: ; ; Q2 = |delta_y| / |delta_x| CLC ; This instruction has no effect as the value of the C ; flag is overridden by the CPY in the following LDY Y1 ; If Y2 < Y1 then skip the following instruction CPY Y2 BCS P%+5 JMP DOWN ; Y2 >= Y1, so jump to DOWN, as we need to draw the line ; to the right and down
Name: LOIN (Part 3 of 7) [Show more] Type: Subroutine Category: Drawing lines Summary: Draw a shallow line going right and up or left and down Deep dive: Bresenham's line algorithm
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine draws a line from (X1, Y1) to (X2, Y2). It has multiple stages. If we get here, then: * The line is going right and up (no swap) or left and down (swap) * X1 < X2 and Y1 > Y2 * Draw from (X1, Y1) at bottom left to (X2, Y2) at top right, omitting the first pixel This routine looks complex, but that's because the loop that's used in the BBC Micro cassette and disc versions has been unrolled to speed it up. The algorithm is unchanged, it's just a lot longer.
LDA X1 ; Each character block contains 8 pixel rows, so to get AND #%11111000 ; the address of the first byte in the character block ; that we need to draw into, as an offset from the start ; of the row, we clear bits 0-2 of the x-coordinate in ; X1 CLC ; The ylookup table lets us look up the 16-bit address ADC ylookupl,Y ; of the start of a character row containing a specific STA SC ; pixel, so this fetches the address for the start of LDA ylookuph,Y ; the character row containing the y-coordinate in Y, ADC #0 ; and adds it to the row offset we just calculated in A STA SC+1 TYA ; Set Y = Y mod 8, which is the pixel row within the AND #7 ; character block at which we want to draw the start of TAY ; our line (as each character block has 8 rows) LDA X1 ; Set X = X1 mod 8, which is the horizontal pixel number AND #7 ; within the character block where the line starts (as TAX ; each pixel line in the character block is 8 pixels ; wide) BIT SWAP ; If SWAP is $FF then we swapped the coordinates above, BMI LI70 ; so jump to LI70 to use the correct addresses LDA LIJT1,X ; Modify the JMP instruction at LI71 to jump to the X-th STA LI71+1 ; unrolled code block below (LI81 through LI88) LDA LIJT2,X ; STA LI71+2 ; This ensures that we start drawing at pixel column X ; within the character block LDX P2 ; Set X = P2 ; = |delta_x| ; ; So we can now use X as the pixel counter .LI71 JMP $8888 ; Jump down to the X-th unrolled code block below ; (i.e. LI81 through LI88) ; ; This instruction is modified by the code above .LI70 LDA LIJT3,X ; Modify the JMP instruction at LI72 to jump to the X-th STA LI72+1 ; unrolled code block below (LI81+6 through LI88+6), LDA LIJT4,X ; skipping the first three instructions so we don't draw STA LI72+2 ; the first pixel ; ; This ensures that we start drawing at pixel column X ; within the character block LDX P2 ; Set X = P2 + 1 INX ; = |delta_x| + 1 ; ; so we can now use X as the pixel counter ; ; We add 1 so we can skip the first pixel plot if the ; line is being drawn with swapped coordinates BEQ LIE1 ; If we have just reached the right end of the line, ; jump to LIE1 to return from the subroutine .LI72 JMP $8888 ; Jump down to the X-th unrolled code block below ; (i.e. LI81+6 through LI88+6) ; ; This instruction is modified by the code above .LIE1 LDY YSAV ; Restore Y from YSAV, so that it's preserved RTS ; Return from the subroutine .LI81 LDA #%10000000 ; Set a mask in A to the first pixel in the 8-pixel byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE1 ; If we have just reached the right end of the line, ; jump to LIE1 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI82 ; If the addition didn't overflow, jump to LI82 to move ; on to the next pixel to draw DEY ; Otherwise we just overflowed, so decrement Y to move ; to the pixel line above BPL LI82-1 ; If Y is positive we are still within the same ; character block, so skip to LI82-1 to move on to the ; next pixel to draw LDA SC ; Otherwise we need to move up into the character block SBC #$40 ; above, so subtract 320 ($140) from SC(1 0) to move up STA SC ; one pixel line, as there are 320 bytes in each LDA SC+1 ; character row in the screen bitmap SBC #$01 STA SC+1 LDY #7 ; Set the pixel line to the last line in the new ; character block CLC ; Clear the C flag, ready for the addition in the next ; part .LI82 LDA #%01000000 ; Set a mask in A to the second pixel in the 8-pixel ; byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE1 ; If we have just reached the right end of the line, ; jump to LIE1 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI83 ; If the addition didn't overflow, jump to LI83 to move ; on to the next pixel to draw DEY ; Otherwise we just overflowed, so decrement Y to move ; to the pixel line above BPL LI83-1 ; If Y is positive we are still within the same ; character block, so skip to LI83-1 to move on to the ; next pixel to draw LDA SC ; Otherwise we need to move up into the character block SBC #$40 ; above, so subtract 320 ($140) from SC(1 0) to move up STA SC ; one pixel line, as there are 320 bytes in each LDA SC+1 ; character row in the screen bitmap SBC #$01 STA SC+1 LDY #7 ; Set the pixel line to the last line in the new ; character block CLC ; Clear the C flag, ready for the addition in the next ; part .LI83 LDA #%00100000 ; Set a mask in A to the third pixel in the 8-pixel byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE1 ; If we have just reached the right end of the line, ; jump to LIE1 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI84 ; If the addition didn't overflow, jump to LI84 to move ; on to the next pixel to draw DEY ; Otherwise we just overflowed, so decrement Y to move ; to the pixel line above BPL LI84-1 ; If Y is positive we are still within the same ; character block, so skip to LI84-1 to move on to the ; next pixel to draw LDA SC ; Otherwise we need to move up into the character block SBC #$40 ; above, so subtract 320 ($140) from SC(1 0) to move up STA SC ; one pixel line, as there are 320 bytes in each LDA SC+1 ; character row in the screen bitmap SBC #$01 STA SC+1 LDY #7 ; Set the pixel line to the last line in the new ; character block CLC ; Clear the C flag, ready for the addition in the next ; part .LI84 LDA #%00010000 ; Set a mask in A to the fourth pixel in the 8-pixel ; byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE1 ; If we have just reached the right end of the line, ; jump to LIE1 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI85 ; If the addition didn't overflow, jump to LI85 to move ; on to the next pixel to draw DEY ; Otherwise we just overflowed, so decrement Y to move ; to the pixel line above BPL LI85-1 ; If Y is positive we are still within the same ; character block, so skip to LI85-1 to move on to the ; next pixel to draw LDA SC ; Otherwise we need to move up into the character block SBC #$40 ; above, so subtract 320 ($140) from SC(1 0) to move up STA SC ; one pixel line, as there are 320 bytes in each LDA SC+1 ; character row in the screen bitmap SBC #$01 STA SC+1 LDY #7 ; Set the pixel line to the last line in the new ; character block CLC ; Clear the C flag, ready for the addition in the next ; part .LI85 LDA #%00001000 ; Set a mask in A to the fifth pixel in the 8-pixel byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE0S ; If we have just reached the right end of the line, ; jump to LIE0 via LIE0S to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI86 ; If the addition didn't overflow, jump to LI86 to move ; on to the next pixel to draw DEY ; Otherwise we just overflowed, so decrement Y to move ; to the pixel line above BPL LI86-1 ; If Y is positive we are still within the same ; character block, so skip to LI86-1 to move on to the ; next pixel to draw LDA SC ; Otherwise we need to move up into the character block SBC #$40 ; above, so subtract 320 ($140) from SC(1 0) to move up STA SC ; one pixel line, as there are 320 bytes in each LDA SC+1 ; character row in the screen bitmap SBC #$01 STA SC+1 LDY #7 ; Set the pixel line to the last line in the new ; character block CLC ; Clear the C flag, ready for the addition in the next ; part .LI86 LDA #%00000100 ; Set a mask in A to the sixth pixel in the 8-pixel byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE0 ; If we have just reached the right end of the line, ; jump to LIE0 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI87 ; If the addition didn't overflow, jump to LI87 to move ; on to the next pixel to draw DEY ; Otherwise we just overflowed, so decrement Y to move ; to the pixel line above BPL LI87-1 ; If Y is positive we are still within the same ; character block, so skip to LI87-1 to move on to the ; next pixel to draw LDA SC ; Otherwise we need to move up into the character block SBC #$40 ; above, so subtract 320 ($140) from SC(1 0) to move up STA SC ; one pixel line, as there are 320 bytes in each LDA SC+1 ; character row in the screen bitmap SBC #$01 STA SC+1 LDY #7 ; Set the pixel line to the last line in the new ; character block CLC ; Clear the C flag, ready for the addition in the next ; part .LI87 LDA #%00000010 ; Set a mask in A to the seventh pixel in the 8-pixel ; byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X .LIE0S BEQ LIE0 ; If we have just reached the right end of the line, ; jump to LIE0 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI88 ; If the addition didn't overflow, jump to LI88 to move ; on to the next pixel to draw DEY ; Otherwise we just overflowed, so decrement Y to move ; to the pixel line above BPL LI88-1 ; If Y is positive we are still within the same ; character block, so skip to LI88-1 to move on to the ; next pixel to draw LDA SC ; Otherwise we need to move up into the character block SBC #$40 ; above, so subtract 320 ($140) from SC(1 0) to move up STA SC ; one pixel line, as there are 320 bytes in each LDA SC+1 ; character row in the screen bitmap SBC #$01 STA SC+1 LDY #7 ; Set the pixel line to the last line in the new ; character block CLC ; Clear the C flag, ready for the addition in the next ; part .LI88 LDA #%00000001 ; Set a mask in A to the eighth pixel in the 8-pixel ; byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE0 ; If we have just reached the right end of the line, ; jump to LIE0 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI89 ; If the addition didn't overflow, jump to LI89 to move ; on to the next pixel to draw DEY ; Otherwise we just overflowed, so decrement Y to move ; to the pixel line above BPL LI89-1 ; If Y is positive we are still within the same ; character block, so skip to LI89-1 to move on to the ; next pixel to draw LDA SC ; Otherwise we need to move up into the character block SBC #$40 ; above, so subtract 320 ($140) from SC(1 0) to move up STA SC ; one pixel line, as there are 320 bytes in each LDA SC+1 ; character row in the screen bitmap SBC #$01 STA SC+1 LDY #7 ; Set the pixel line to the last line in the new ; character block CLC ; Clear the C flag, ready for the addition in the next ; part .LI89 LDA SC ; Add 8 to SC(1 0), starting with the low byte, so SC ADC #8 ; now points to the next character along to the right STA SC BCS P%+5 ; If the addition just overflowed then skip the next ; instruction as we need to increment the high byte JMP LI81 ; Loop back to draw the next character along to the ; right INC SC+1 ; Increment the high byte of SC(1 0), so SC now points ; to the next character along to the right JMP LI81 ; Loop back to draw the next character along to the ; right .LIE0 LDY YSAV ; Restore Y from YSAV, so that it's preserved RTS ; Return from the subroutine
Name: LOIN (Part 4 of 7) [Show more] Type: Subroutine Category: Drawing lines Summary: Draw a shallow line going right and down or left and up Deep dive: Bresenham's line algorithm
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine draws a line from (X1, Y1) to (X2, Y2). It has multiple stages. If we get here, then: * The line is going right and down (no swap) or left and up (swap) * X1 < X2 and Y1 <= Y2 * Draw from (X1, Y1) at top left to (X2, Y2) at bottom right, omitting the first pixel This routine looks complex, but that's because the loop that's used in the BBC Micro cassette and disc versions has been unrolled to speed it up. The algorithm is unchanged, it's just a lot longer.
.DOWN LDA ylookuph,Y ; Set the top byte of SC(1 0) to the address of the STA SC+1 ; start of the character row to draw in, from the ; ylookup table LDA X1 ; Each character block contains 8 pixel rows, so to get AND #%11111000 ; the address of the first byte in the character block ; that we need to draw into, as an offset from the start ; of the row, we clear bits 0-2 of the x-coordinate in ; X1 ADC ylookupl,Y ; The ylookup table lets us look up the 16-bit address STA SC ; of the start of a character row containing a specific BCC P%+5 ; pixel, so this fetches the address for the start of INC SC+1 ; the character row containing the y-coordinate in Y, ; and adds it to the row offset we just calculated in A CLC ; Calculate SC(1 0) = SC(1 0) - 248 SBC #247 ; STA SC ; This enables us to decrement Y towards zero to work BCS P%+4 ; through the character block - see the next comment for DEC SC+1 ; details TYA ; Set bits 3-7 of Y, which contains the pixel row within AND #%00000111 ; the character, and is therefore in the range 0-7, so EOR #%11111000 ; this does Y = 248 + Y TAY ; ; We therefore have the following: ; ; SC(1 0) + Y = SC(1 0) - 248 + 248 + Y ; = SC(1 0) + Y ; ; so the screen location we poke hasn't changed, but Y ; is now a larger number and SC is smaller. This means ; we can increment Y to move down a line, as per usual, ; but we can test for when it reaches the bottom of the ; character block with a simple BEQ rather than checking ; whether it's reached 8, so this appears to be a code ; optimisation ; ; If it helps, you can think of Y as being a negative ; number that we are incrementing towards zero as we ; move along the line - we just need to alter the value ; of SC so that SC(1 0) + Y points to the right address LDA X1 ; Set X = X1 mod 8, which is the horizontal pixel number AND #7 ; within the character block where the line starts (as TAX ; each pixel line in the character block is 8 pixels ; wide) BIT SWAP ; If SWAP is $FF then we swapped the coordinates above, BMI LI90 ; so jump to LI90 to use the correct addresses LDA LIJT5,X ; Modify the JMP instruction at LI91 to jump to the X-th STA LI91+1 ; unrolled code block below (LI21 through LI28) LDA LIJT6,X ; STA LI91+2 ; This ensures that we start drawing at pixel column X ; within the character block LDX P2 ; Set X = P2 ; = |delta_x| ; ; So we can now use X as the pixel counter BEQ LIE0 ; If we have already reached the right end of the line, ; jump to LIE0 to return from the subroutine .LI91 JMP $8888 ; Jump down to the X-th unrolled code block below ; (i.e. LI21 through LI28) ; ; This instruction is modified by the code above .LI90 LDA LIJT7,X ; Modify the JMP instruction at LI92 to jump to the X-th STA LI92+1 ; unrolled code block below (LI21+6 through LI28+6), LDA LIJT8,X ; skipping the first three instructions so we don't draw STA LI92+2 ; the first pixel ; ; This ensures that we start drawing at pixel column X ; within the character block LDX P2 ; Set X = P2 + 1 INX ; = |delta_x| + 1 ; ; so we can now use X as the pixel counter ; ; We add 1 so we can skip the first pixel plot if the ; line is being drawn with swapped coordinates BEQ LIE0 ; If we have just reached the right end of the line, ; jump to LIE0 to return from the subroutine .LI92 JMP $8888 ; Jump down to the X-th unrolled code block below ; (i.e. LI21+6 through LI28+6) ; ; This instruction is modified by the code above .LIE3 LDY YSAV ; Restore Y from YSAV, so that it's preserved RTS ; Return from the subroutine .LI21 LDA #%10000000 ; Set a mask in A to the first pixel in the 8-pixel byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE3 ; If we have just reached the right end of the line, ; jump to LIE3 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI22 ; If the addition didn't overflow, jump to LI22 to move ; on to the next pixel to draw INY ; Otherwise we just overflowed, so increment Y to move ; to the pixel line below BNE LI22-1 ; If Y < 0 then we are still within the same character ; block, so skip to LI22-1 to clear the C flag and move ; on to the next pixel to draw LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each character LDA SC+1 ; row in the screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BCC, so we only need to add $13F to get the result LDY #248 ; Set the pixel line in Y to the first line in that ; character block (as we subtracted 248 from SC above) CLC ; Clear the C flag, ready for the addition in the next ; part .LI22 LDA #%01000000 ; Set a mask in A to the second pixel in the 8-pixel ; byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE3 ; If we have just reached the right end of the line, ; jump to LIE3 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI23 ; If the addition didn't overflow, jump to LI23 to move ; on to the next pixel to draw INY ; Otherwise we just overflowed, so increment Y to move ; to the pixel line below BNE LI23-1 ; If Y < 0 then we are still within the same character ; block, so skip to LI23-1 to clear the C flag and move ; on to the next pixel to draw LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each character LDA SC+1 ; row in the screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BCC, so we only need to add $13F to get the result LDY #248 ; Set the pixel line in Y to the first line in that ; character block (as we subtracted 248 from SC above) CLC ; Clear the C flag, ready for the addition in the next ; part .LI23 LDA #%00100000 ; Set a mask in A to the third pixel in the 8-pixel byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE3 ; If we have just reached the right end of the line, ; jump to LIE3 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI24 ; If the addition didn't overflow, jump to LI24 to move ; on to the next pixel to draw INY ; Otherwise we just overflowed, so increment Y to move ; to the pixel line below BNE LI24-1 ; If Y < 0 then we are still within the same character ; block, so skip to LI24-1 to clear the C flag and move ; on to the next pixel to draw LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each row in the LDA SC+1 ; screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BCC, so we only need to add $13F to get the result LDY #248 ; Set the pixel line in Y to the first line in that ; character block (as we subtracted 248 from SC above) CLC ; Clear the C flag, ready for the addition in the next ; part .LI24 LDA #%00010000 ; Set a mask in A to the fourth pixel in the 8-pixel ; byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE2S ; If we have just reached the right end of the line, ; jump to LIE2 via LIE2S to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI25 ; If the addition didn't overflow, jump to LI25 to move ; on to the next pixel to draw INY ; Otherwise we just overflowed, so increment Y to move ; to the pixel line below BNE LI25-1 ; If Y < 0 then we are still within the same character ; block, so skip to LI25-1 to clear the C flag and move ; on to the next pixel to draw LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each row in the LDA SC+1 ; screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BCC, so we only need to add $13F to get the result LDY #248 ; Set the pixel line in Y to the first line in that ; character block (as we subtracted 248 from SC above) CLC ; Clear the C flag, ready for the addition in the next ; part .LI25 LDA #%00001000 ; Set a mask in A to the fifth pixel in the 8-pixel byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE2S ; If we have just reached the right end of the line, ; jump to LIE2 via LIE2S to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI26 ; If the addition didn't overflow, jump to LI26 to move ; on to the next pixel to draw INY ; Otherwise we just overflowed, so increment Y to move ; to the pixel line below BNE LI26-1 ; If Y < 0 then we are still within the same character ; block, so skip to LI26-1 to clear the C flag and move ; on to the next pixel to draw LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each character LDA SC+1 ; row in the screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BCC, so we only need to add $13F to get the result LDY #248 ; Set the pixel line in Y to the first line in that ; character block (as we subtracted 248 from SC above) CLC ; Clear the C flag, ready for the addition in the next ; part .LI26 LDA #%00000100 ; Set a mask in A to the sixth pixel in the 8-pixel byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE2 ; If we have just reached the right end of the line, ; jump to LIE2 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI27 ; If the addition didn't overflow, jump to LI27 to move ; on to the next pixel to draw INY ; Otherwise we just overflowed, so increment Y to move ; to the pixel line below BNE LI27-1 ; If Y < 0 then we are still within the same character ; block, so skip to LI27-1 to clear the C flag and move ; on to the next pixel to draw LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each character LDA SC+1 ; row in the screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BCC, so we only need to add $13F to get the result LDY #248 ; Set the pixel line in Y to the first line in that ; character block (as we subtracted 248 from SC above) CLC ; Clear the C flag, ready for the addition in the next ; part .LI27 LDA #%00000010 ; Set a mask in A to the seventh pixel in the 8-pixel EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X .LIE2S BEQ LIE2 ; If we have just reached the right end of the line, ; jump to LIE2 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI28 ; If the addition didn't overflow, jump to LI28 to move ; on to the next pixel to draw INY ; Otherwise we just overflowed, so increment Y to move ; to the pixel line below BNE LI28-1 ; If Y < 0 then we are still within the same character ; block, so skip to LI28-1 to clear the C flag and move ; on to the next pixel to draw LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each character LDA SC+1 ; row in the screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BCC, so we only need to add $13F to get the result LDY #248 ; Set the pixel line in Y to the first line in that ; character block (as we subtracted 248 from SC above) CLC ; Clear the C flag, ready for the addition in the next ; part .LI28 LDA #%00000001 ; Set a mask in A to the eighth pixel in the 8-pixel ; byte EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEX ; Decrement the counter in X BEQ LIE2 ; If we have just reached the right end of the line, ; jump to LIE2 to return from the subroutine LDA S2 ; Set S2 = S2 + Q2 to update the slope error ADC Q2 STA S2 BCC LI29 ; If the addition didn't overflow, jump to LI29 to move ; on to the next pixel to draw INY ; Otherwise we just overflowed, so increment Y to move ; to the pixel line below BNE LI29-1 ; If Y < 0 then we are still within the same character ; block, so skip to LI29-1 to clear the C flag and move ; on to the next pixel to draw LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each character LDA SC+1 ; row in the screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BCC, so we only need to add $13F to get the result LDY #248 ; Set the pixel line in Y to the first line in that ; character block (as we subtracted 248 from SC above) CLC ; Clear the C flag, ready for the addition in the next ; part .LI29 LDA SC ; Add 8 to SC(1 0), starting with the low byte, so SC ADC #8 ; now points to the next character along to the right STA SC BCC P%+4 ; If the addition didn't overflow, skip the following ; instruction INC SC+1 ; Increment the high byte of SC(1 0), so SC now points ; to the next character along to the right JMP LI21 ; Loop back to draw the next character along to the ; right .LIE2 LDY YSAV ; Restore Y from YSAV, so that it's preserved RTS ; Return from the subroutine
Name: LOIN (Part 5 of 7) [Show more] Type: Subroutine Category: Drawing lines Summary: Draw a line: Line has a steep gradient, step up along y-axis Deep dive: Bresenham's line algorithm
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine draws a line from (X1, Y1) to (X2, Y2). It has multiple stages. If we get here, then: * |delta_y| >= |delta_x| * The line is closer to being vertical than horizontal * We are going to step up along the y-axis * We potentially swap coordinates to make sure Y1 >= Y2
.STPY LDY Y1 ; Set A = Y = Y1 TYA LDX X1 ; Set X = X1 CPY Y2 ; If Y1 >= Y2, jump down to LI15, as the coordinates are BCS LI15 ; already in the order that we want DEC SWAP ; Otherwise decrement SWAP from 0 to $FF, to denote that ; we are swapping the coordinates around LDA X2 ; Swap the values of X1 and X2 STA X1 STX X2 TAX ; Set X = X1 LDA Y2 ; Swap the values of Y1 and Y2 STA Y1 STY Y2 TAY ; Set Y = A = Y1 .LI15 ; By this point we know the line is vertical-ish and ; Y1 >= Y2, so we're going from top to bottom as we go ; from Y1 to Y2 TXA ; Set A = bits 3-7 of X1 AND #%11111000 CLC ; The ylookup table lets us look up the 16-bit address ADC ylookupl,Y ; of the start of a character row containing a specific STA SC ; pixel, so this fetches the address for the start of LDA ylookuph,Y ; the character row containing the y-coordinate in Y, ADC #0 ; and adds it to the row offset we just calculated in A STA SC+1 TYA ; Set Y = Y mod 8 AND #7 ; TAY ; So Y is the pixel row within the character block where ; we want to start drawing TXA ; Set X = X1 mod 8, which is the horizontal pixel number AND #7 ; within the character block where the line starts (as TAX ; each pixel line in the character block is 8 pixels ; wide) LDA TWOS,X ; Fetch a 1-pixel byte from TWOS where pixel X is set, STA R2 ; and store it in R2 ; The following section calculates: ; ; P2 = P2 / Q2 ; = |delta_x| / |delta_y| ; ; using the log tables at logL and log to calculate: ; ; A = log(P2) - log(Q2) ; = log(|delta_x|) - log(|delta_y|) ; ; by first subtracting the low bytes of the logarithms ; from the table at LogL, and then subtracting the high ; bytes from the table at log, before applying the ; antilog to get the result of the division and putting ; it in P2 LDX P2 ; Set X = |delta_x| BEQ LIfudge ; If |delta_x| = 0, jump to LIfudge to return 0 as the ; result of the division LDA logL,X ; Set A = log(P2) - log(Q2) LDX Q2 ; = log(|delta_x|) - log(|delta_y|) SEC ; SBC logL,X ; by first subtracting the low bytes of ; log(P2) - log(Q2) BMI LIloG ; If A > 127, jump to LIloG LDX P2 ; And then subtracting the high bytes of LDA log,X ; log(P2) - log(Q2) so now A contains the high byte of LDX Q2 ; log(P2) - log(Q2) SBC log,X BCS LIlog3 ; If the subtraction fitted into one byte and didn't ; underflow, then log(P2) - log(Q2) < 256, so we jump to ; LIlog3 to return a result of 255 TAX ; Otherwise we set A to the A-th entry from the antilog LDA antilog,X ; table so the result of the division is now in A JMP LIlog2 ; Jump to LIlog2 to return the result .LIlog3 LDA #255 ; The division is very close to 1, so set A to the BNE LIlog2 ; closest possible answer to 256, i.e. 255, and jump to ; LIlog2 to return the result (this BNE is effectively a ; JMP as A is never zero) .LIloG LDX P2 ; Subtract the high bytes of log(P2) - log(Q2) so now A LDA log,X ; contains the high byte of log(P2) - log(Q2) LDX Q2 SBC log,X BCS LIlog3 ; If the subtraction fitted into one byte and didn't ; underflow, then log(P2) - log(Q2) < 256, so we jump to ; LIlog3 to return a result of 255 TAX ; Otherwise we set A to the A-th entry from the LDA antilogODD,X ; antilogODD so the result of the division is now in A .LIlog2 STA P2 ; Store the result of the division in P, so we have: ; ; P2 = |delta_x| / |delta_y| .LIfudge SEC ; Set the C flag for the subtraction below LDX Q2 ; Set X = Q2 + 1 INX ; = |delta_y| + 1 ; ; We add 1 so we can skip the first pixel plot if the ; line is being drawn with swapped coordinates LDA X2 ; Set A = X2 - X1 SBC X1 BCC LFT ; If X2 < X1 then jump to LFT, as we need to draw the ; line to the left and down
Name: LOIN (Part 6 of 7) [Show more] Type: Subroutine Category: Drawing lines Summary: Draw a steep line going up and left or down and right Deep dive: Bresenham's line algorithm
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine draws a line from (X1, Y1) to (X2, Y2). It has multiple stages. If we get here, then: * The line is going up and left (no swap) or down and right (swap) * X1 < X2 and Y1 >= Y2 * Draw from (X1, Y1) at top left to (X2, Y2) at bottom right, omitting the first pixel
CLC ; Clear the C flag LDA SWAP ; If SWAP = 0 then we didn't swap the coordinates above, BEQ LI17 ; so jump down to LI17 to skip plotting the first pixel DEX ; Decrement the counter in X because we're about to plot ; the first pixel .LIL5 ; We now loop along the line from left to right, using X ; as a decreasing counter, and at each count we plot a ; single pixel using the pixel mask in R2 LDA R2 ; Fetch the pixel byte from R2 EOR (SC),Y ; Store R into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen .LI17 DEY ; Decrement Y to step up along the y-axis BPL LI16 ; If Y is positive we are still within the same ; character block, so skip to LI16 ; We now need to move up into the character block above, ; and each character row in screen memory takes up $140 ; bytes ($100 for the visible part and $20 for each of ; the blank borders on the side of the screen), so ; that's what we need to subtract from SC(1 0) ; ; We also know the C flag is clear, as we cleared it ; above, so we can subtract $13F in order to get the ; correct result LDA SC ; Set SC(1 0) = SC(1 0) - $140 SBC #$3F ; STA SC ; Starting with the low bytes LDA SCH ; And then subtracting the high bytes SBC #$01 STA SCH LDY #7 ; Set the pixel line to the last line in that character ; block .LI16 LDA S2 ; Set S2 = S2 + P2 to update the slope error ADC P2 STA S2 BCC LIC5 ; If the addition didn't overflow, jump to LIC5 LSR R2 ; Otherwise we just overflowed, so shift the single ; pixel in R2 to the right, so the next pixel we plot ; will be at the next x-coordinate along BCC LIC5 ; If the pixel didn't fall out of the right end of R ; into the C flag, then jump to LIC5 ROR R2 ; Otherwise we need to move over to the next character ; block, so first rotate R right so the set C flag goes ; back into the left end, giving %10000000 LDA SC ; Add 8 to SC, so SC(1 0) now points to the next ADC #8 ; character along to the right STA SC BCC LIC5 ; If the addition of the low bytes of SC overflowed, INC SC+1 ; increment the high byte CLC ; Clear the C flag .LIC5 DEX ; Decrement the counter in X BNE LIL5 ; If we haven't yet reached the right end of the line, ; loop back to LIL5 to plot the next pixel along LDY YSAV ; Restore Y from YSAV, so that it's preserved RTS ; Return from the subroutine
Name: LOIN (Part 7 of 7) [Show more] Type: Subroutine Category: Drawing lines Summary: Draw a steep line going up and right or down and left Deep dive: Bresenham's line algorithm
Context: See this subroutine on its own page References: This subroutine is called as follows: * HLOIN calls via HL6

This routine draws a line from (X1, Y1) to (X2, Y2). It has multiple stages. If we get here, then: * The line is going up and right (no swap) or down and left (swap) * X1 >= X2 and Y1 >= Y2 * Draw from (X1, Y1) at bottom left to (X2, Y2) at top right, omitting the first pixel
Other entry points: HL6 Contains an RTS
.LFT LDA SWAP ; If SWAP = 0 then we didn't swap the coordinates above, BEQ LI18 ; so jump down to LI18 to skip plotting the first pixel DEX ; Decrement the counter in X because we're about to plot ; the first pixel .LIL6 LDA R2 ; Fetch the pixel byte from R2 EOR (SC),Y ; Store R into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen .LI18 DEY ; Decrement Y to step up along the y-axis BPL LI19 ; If Y is positive we are still within the same ; character block, so skip to LI19 ; We now need to move up into the character block above, ; and each character row in screen memory takes up $140 ; bytes ($100 for the visible part and $20 for each of ; the blank borders on the side of the screen), so ; that's what we need to subtract from SC(1 0) ; ; We also know the C flag is clear, as we call LFT with ; a BCC, so we can subtract $13F in order to get the ; correct result LDA SC ; Set SC(1 0) = SC(1 0) - $140 SBC #$3F ; STA SC ; Starting with the low bytes LDA SCH ; And then subtracting the high bytes SBC #$01 STA SCH LDY #7 ; Set the pixel line to the last line in that character ; block .LI19 LDA S2 ; Set S2 = S2 + P2 to update the slope error ADC P2 STA S2 BCC LIC6 ; If the addition didn't overflow, jump to LIC6 ASL R2 ; Otherwise we just overflowed, so shift the single ; pixel in R2 to the left, so the next pixel we plot ; will be at the previous x-coordinate BCC LIC6 ; If the pixel didn't fall out of the left end of R2 ; into the C flag, then jump to LIC6 ROL R2 ; Otherwise we need to move over to the next character ; block, so first rotate R2 left so the set C flag goes ; back into the right end, giving %0000001 LDA SC ; Subtract 7 from SC, so SC(1 0) now points to the SBC #7 ; previous character along to the left STA SC BCS P%+4 ; If the subtraction of the low bytes of SC underflowed, DEC SCH ; decrement the high byte CLC ; Clear the C flag so it doesn't affect the additions ; below .LIC6 DEX ; Decrement the counter in X BNE LIL6 ; If we haven't yet reached the left end of the line, ; loop back to LIL6 to plot the next pixel along LDY YSAV ; Restore Y from YSAV, so that it's preserved .HL6 RTS ; Return from the subroutine
Name: HLOIN [Show more] Type: Subroutine Category: Drawing lines Summary: Draw a horizontal line from (X1, Y1) to (X2, Y1)
Context: See this subroutine on its own page References: This subroutine is called as follows: * BOXS calls HLOIN * HLOIN2 calls HLOIN * SUN (Part 3 of 4) calls HLOIN
.HLOIN STY YSAV ; Store Y into YSAV, so we can preserve it across the ; call to this subroutine LDX X1 ; Set X = X1 CPX X2 ; If X1 = X2 then the start and end points are the same, BEQ HL6 ; so return from the subroutine (as HL6 contains an RTS) BCC HL5 ; If X1 < X2, jump to HL5 to skip the following code, as ; (X1, Y1) is already the left point LDA X2 ; Swap the values of X1 and X2, so we know that (X1, Y1) STA X1 ; is on the left and (X2, Y1) is on the right STX X2 TAX ; Set X = X1 .HL5 DEC X2 ; Decrement X2 so we do not draw a pixel at the end ; point LDA Y1 ; Set the low byte of SC(1 0) to Y1 mod 8, which is the TAY ; pixel row within the character block at which we want AND #7 ; to draw our line (as each character block has 8 rows) STA SC LDA ylookuph,Y ; Set the top byte of SC(1 0) to the address of the STA SC+1 ; start of the character row to draw in, from the ; ylookup table TXA ; Set A = bits 3-7 of X1 AND #%11111000 CLC ; The ylookup table lets us look up the 16-bit address ADC ylookupl,Y ; of the start of a character row containing a specific TAY ; pixel, so this fetches the address for the start of ; the character row containing the y-coordinate in Y, ; and adds it to the row offset we just calculated in A, ; storing the result in Y BCC P%+4 ; If the addition overflowed, increment the high byte INC SC+1 ; of SC(1 0), so SC(1 0) + Y gives us the correct ; address of the start of the line .HL1 TXA ; Set T2 = bits 3-7 of X1, which will contain the AND #%11111000 ; character number of the start of the line * 8 STA T2 LDA X2 ; Set A = bits 3-7 of X2, which will contain the AND #%11111000 ; character number of the end of the line * 8 SEC ; Set A = A - T2, which will contain the number of SBC T2 ; character blocks we need to fill - 1 * 8 BEQ HL2 ; If A = 0 then the start and end character blocks are ; the same, so the whole line fits within one block, so ; jump down to HL2 to draw the line ; Otherwise the line spans multiple characters, so we ; start with the left character, then do any characters ; in the middle, and finish with the right character LSR A ; Set R2 = A / 8, so R2 now contains the number of LSR A ; character blocks we need to fill - 1 LSR A STA R2 LDA X1 ; Set X = X1 mod 8, which is the horizontal pixel number AND #7 ; within the character block where the line starts (as TAX ; each pixel line in the character block is 8 pixels ; wide) LDA TWFR,X ; Fetch a ready-made byte with X pixels filled in at the ; right end of the byte (so the filled pixels start at ; point X and go all the way to the end of the byte), ; which is the shape we want for the left end of the ; line EOR (SC),Y ; Store this into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen, ; so we have now drawn the line's left cap TYA ; Set Y = Y + 8 so (SC),Y points to the next character ADC #8 ; block along, on the same pixel row as before TAY BCC P%+4 ; If the addition overflowed, increment the high byte INC SC+1 ; of SC(1 0), so SC(1 0) + Y gives us the correct ; address of the pixel LDX R2 ; Fetch the number of character blocks we need to fill ; from R2 DEX ; Decrement the number of character blocks in X BEQ HL3 ; If X = 0 then we only have the last block to do (i.e. ; the right cap), so jump down to HL3 to draw it CLC ; Otherwise clear the C flag so we can do some additions ; while we draw the character blocks with full-width ; lines in them .HLL1 LDA #%11111111 ; Store a full-width 8-pixel horizontal line in SC(1 0) EOR (SC),Y ; so that it draws the line on-screen, using EOR logic STA (SC),Y ; so it merges with whatever is already on-screen TYA ; Set Y = Y + 8 so (SC),Y points to the next character ADC #8 ; block along, on the same pixel row as before TAY BCC P%+5 ; If the addition overflowed, increment the high byte INC SC+1 ; of SC(1 0), so SC(1 0) + Y gives us the correct CLC ; address of the start of the line ; ; We also clear the C flag so additions will work ; properly if we loop back for more DEX ; Decrement the number of character blocks in X BNE HLL1 ; Loop back to draw more full-width lines, if we have ; any more to draw .HL3 LDA X2 ; Now to draw the last character block at the right end AND #7 ; of the line, so set X = X2 mod 8, which is the TAX ; horizontal pixel number where the line ends LDA TWFL,X ; Fetch a ready-made byte with X pixels filled in at the ; left end of the byte (so the filled pixels start at ; the left edge and go up to point X), which is the ; shape we want for the right end of the line EOR (SC),Y ; Store this into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen, ; so we have now drawn the line's right cap LDY YSAV ; Restore Y from YSAV, so that it's preserved across the ; call to this subroutine RTS ; Return from the subroutine .HL2 ; If we get here then the entire horizontal line fits ; into one character block LDA X1 ; Set X = X1 mod 8, which is the horizontal pixel number AND #7 ; within the character block where the line starts (as TAX ; each pixel line in the character block is 8 pixels ; wide) LDA TWFR,X ; Fetch a ready-made byte with X pixels filled in at the STA T2 ; right end of the byte (so the filled pixels start at ; point X and go all the way to the end of the byte) LDA X2 ; Set X = X2 mod 8, which is the horizontal pixel number AND #7 ; where the line ends TAX LDA TWFL,X ; Fetch a ready-made byte with X pixels filled in at the ; left end of the byte (so the filled pixels start at ; the left edge and go up to point X) AND T2 ; We now have two bytes, one (T2) containing pixels from ; the starting point X1 onwards, and the other (A) ; containing pixels up to the end point at X2, so we can ; get the actual line we want to draw by AND'ing them ; together. For example, if we want to draw a line from ; point 2 to point 5 (within the row of 8 pixels ; numbered from 0 to 7), we would have this: ; ; T2 = %00111111 ; A = %11111100 ; T2 AND A = %00111100 ; ; So we can stick T2 AND A in screen memory to get the ; line we want, which is what we do here by setting ; A = A AND T2 EOR (SC),Y ; Store our horizontal line byte into screen memory at STA (SC),Y ; SC(1 0), using EOR logic so it merges with whatever is ; already on-screen LDY YSAV ; Restore Y from YSAV, so that it's preserved RTS ; Return from the subroutine EQUD $F0E0C080 ; These bytes appear to be unused; they contain a copy EQUW $FCF8 ; of the TWFL variable, and the original source has a EQUB $FE ; commented out label .TWFL EQUD $1F3F7FFF ; These bytes appear to be unused; they contain a copy EQUD $0103070F ; of the TWFR variable, and the original source has a ; commented out label .TWFR
Name: DOT [Show more] Type: Subroutine Category: Dashboard Summary: Draw a dash on the compass
Context: See this subroutine on its own page References: This subroutine is called as follows: * COMPAS calls DOT * SP2 calls DOT

Arguments: COMX The screen pixel x-coordinate of the dash COMY The screen pixel y-coordinate of the dash COMC The colour and thickness of the dash: * #YELLOW = a double-height dash in yellow, for when the object in the compass is in front of us * #GREEN = a single-height dash in green, for when the object in the compass is behind us
.DOT LDA COMY ; Set Y1 = COMY, the y-coordinate of the dash STA Y1 LDA COMX ; Set X1 = COMX, the x-coordinate of the dash STA X1 LDA COMC ; Set COL = COMC, the mode 5 colour byte for the dash STA COL CMP #YELLOW ; If the dash's colour is not yellow, jump to CPIX2 to BNE CPIX2 ; draw a single-height dash in the compass, as it is ; showing that the planet or station is behind us ; Otherwise the dash is yellow, which is in front of us, ; so fall through into CPIX4 to draw a double-height ; dash in the compass
Name: CPIX4 [Show more] Type: Subroutine Category: Drawing pixels Summary: Draw a double-height dot on the dashboard
Context: See this subroutine on its own page References: This subroutine is called as follows: * SCAN calls CPIX4

Draw a double-height dot (2 pixels high, 2 pixels wide).
Arguments: X1 The screen pixel x-coordinate of the bottom-left corner of the dot Y1 The screen pixel y-coordinate of the bottom-left corner of the dot COL The colour of the dot as a character row byte
.CPIX4 JSR CPIX2 ; Call CPIX2 to draw a single-height dash at (X1, Y1) DEC Y1 ; Decrement Y1 ; Fall through into CPIX2 to draw a second single-height ; dash on the pixel row above the first one, to create a ; double-height dot
Name: CPIX2 [Show more] Type: Subroutine Category: Drawing pixels Summary: Draw a single-height dash on the dashboard
Context: See this subroutine on its own page References: This subroutine is called as follows: * CPIX4 calls CPIX2 * DOT calls CPIX2

Draw a single-height multicolour bitmap mode dash (1 pixel high, 2 pixels wide).
Arguments: X1 The screen pixel x-coordinate of the dash Y1 The screen pixel y-coordinate of the dash COL The colour of the dash as a multicolour bitmap mode character row byte
.CPIX2 LDY Y1 ; Fetch the y-coordinate into Y LDA X1 ; Each character block contains 8 pixel rows, so to get AND #%11111000 ; the address of the first byte in the character block ; that we need to draw into, as an offset from the start ; of the row, we clear bits 0-2 CLC ; The ylookup table lets us look up the 16-bit address ADC ylookupl,Y ; of the start of a character row containing a specific STA SC ; pixel, so this fetches the address for the start of LDA ylookuph,Y ; the character row containing the y-coordinate in Y, ADC #0 ; and adds it to the row offset we just calculated in A STA SC+1 TYA ; Set Y to the y-coordinate mod 8, which will be the AND #7 ; number of the pixel row we need to draw within the TAY ; character block LDA X1 ; Set X = X1 mod 8, which is the horizontal pixel number AND #7 ; within the character block where the pixel lies (as TAX ; each pixel line in the character block is 8 pixels ; wide) LDA CTWOS2,X ; Fetch a multicolour bitmap mode 1-pixel byte with the AND COL ; pixel position at X, and AND with the colour byte so ; that pixel takes on the colour we want to draw (i.e. A ; is acting as a mask on the colour byte) ; ; Note that the CTWOS2 table contains two identical ; bitmap bytes for consecutive values of X, as each ; pixel is double-width and straddles two x-coordinates EOR (SC),Y ; Draw the pixel on-screen using EOR logic, so we can STA (SC),Y ; remove it later without ruining the background that's ; already on-screen ;JSR P%+3 ; These instructions are commented out in the original ;INX ; source LDA CTWOS2+2,X ; Fetch a multicolour bitmap mode 1-pixel byte with the ; pixel position at X+1, so we can draw the right pixel ; of the dash (we add 2 to CTWOS2 as there are two ; repeated entries for X and X+1 in the table) BPL CP1 ; The CTWOS table has an extra two rows at the end of it ; that repeat the first two value, %11000000, so if we ; have not fetched that value, then the right pixel of ; the dash is in the same character block as the left ; pixel, so jump to CP1 to draw it LDA SC ; Otherwise the left pixel we drew was at the last CLC ; position of four in this character block, so we add ADC #8 ; 8 to the screen address to move onto the next block STA SC ; along (as there are 8 bytes in a character block) BCC P%+4 ; If the addition we just did overflowed, then increment INC SC+1 ; the high byte of SC(1 0), as this means we just moved ; into the right half of the screen row LDA CTWOS2+2,X ; Re-fetch the multicolour bitmap mode 1-pixel byte, as ; we just overwrote A (the byte will still be the last ; byte from the table, which is correct as we want to ; draw the leftmost pixel in the next character along as ; the dash's right pixel) .CP1 AND COL ; Apply the colour mask to the pixel byte, as above EOR (SC),Y ; Draw the dash's right pixel according to the mask in STA (SC),Y ; A, with the colour in COL, using EOR logic, just as ; above RTS ; Return from the subroutine
Name: ECBLB2 [Show more] Type: Subroutine Category: Dashboard Summary: Start up the E.C.M. (light up the indicator, start the countdown and make the E.C.M. sound)
Context: See this subroutine on its own page References: This subroutine is called as follows: * Main flight loop (Part 3 of 16) calls ECBLB2 * TACTICS (Part 1 of 7) calls ECBLB2
.ECBLB2 LDA #32 ; Set the E.C.M. countdown timer in ECMA to 32 STA ECMA LDY #sfxecm ; Call the NOISE routine with Y = sfxecm to make the JSR NOISE ; sound of the E.C.M., returning from the subroutine ; using a tail call ; Fall through into ECBLB to light up the E.C.M. bulb
Name: ECBLB [Show more] Type: Subroutine Category: Dashboard Summary: Light up the E.C.M. indicator bulb ("E") on the dashboard
Context: See this subroutine on its own page References: This subroutine is called as follows: * ECMOF calls ECBLB
.ECBLB LDA ECELL ; EOR the colour byte at ECELL with the colour of the EOR #BULBCOL ; E.C.M. indicator bulb, so this either zeroes the STA ECELL ; character block for the top part of the E.C.M. bulb, ; which will hide it, or it sets it to BULBCOL, which ; will show it (so this toggles the top part of the ; E.C.M. bulb) LDA ECELL+40 ; Do the same for the bottom part of the E.C.M. bulb EOR #BULBCOL STA ECELL+40 RTS ; Return from the subroutine
Name: SPBLB [Show more] Type: Subroutine Category: Dashboard Summary: Light up the space station indicator ("S") on the dashboard
Context: See this subroutine on its own page References: This subroutine is called as follows: * KS4 calls SPBLB * NWSPS calls SPBLB * RES2 calls SPBLB
.SPBLB LDA SCELL ; EOR the colour byte at SCELL with the colour of the EOR #BULBCOL ; space station indicator bulb, so this either zeroes STA SCELL ; the character block for the top part of the space ; station bulb, which will hide it, or it sets it to ; BULBCOL, which will show it (so this toggles the top ; part of the space station bulb) LDA SCELL+40 ; Do the same for the bottom part of the space station EOR #BULBCOL ; bulb STA SCELL+40 RTS ; Return from the subroutine
Name: MSBAR [Show more] Type: Subroutine Category: Dashboard Summary: Draw a specific indicator in the dashboard's missile bar
Context: See this subroutine on its own page References: This subroutine is called as follows: * ABORT2 calls MSBAR * Main flight loop (Part 3 of 16) calls MSBAR * msblob calls MSBAR

Each indicator is a character block, so we can change the colour by simply changing the relevant colour byte
Arguments: X The number of the missile indicator to update (counting from right to left, so indicator NOMSL is the leftmost indicator) Y The colour of the missile indicator: * #BLACK2 = black (no missile) * #RED2 = red (armed and locked) * #YELLOW2 = yellow/white (armed) * #GREEN2 = green (disarmed)
Returns: X X is preserved Y Y is set to 0
.MSBAR DEX ; Set A = X - 1 TXA ; INX ; So A is in the range 0 to 3, with 0 being the missile ; indicator on the right EOR #3 ; Flip A so it is in the range 0 to 3, but with 0 being ; the missile indicator on the left STY SC ; Swap A and Y around (using SC as temporary storage), TAY ; so we have: LDA SC ; ; * A = the colour of the missile indicator ; ; * Y = the indicator number (0 on left, 3 on right) STA MCELL,Y ; Set the Y-th colour byte at MCELL to the new colour of ; the indicator, which sets the colour of the character ; block for the Y-th indicator LDY #0 ; Set Y = 0 so we can return it from the subroutine RTS ; Return from the subroutine
Name: newosrdch [Show more] Type: Subroutine Category: Tube Summary: The custom OSRDCH routine for reading characters Deep dive: 6502 Second Processor Tube communication
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine is not used in this version of Elite. It is left over from the 650s Second Processor version.
.newosrdch JSR $FFFF ; This address is overwritten by the STARTUP routine to ; contain the original value of RDCHV, so this call acts ; just like a standard JSR OSRDCH call, and reads a ; character from the current input stream and stores it ; in A CMP #128 ; If A < 128 then skip the following three instructions, BCC P%+6 ; otherwise the character is invalid, so fall through ; into badkey to deal with it .badkey ; If we get here then the character we read is invalid, ; so we return a beep character LDA #7 ; Set A to the beep character CLC ; Clear the C flag RTS ; Return from the subroutine ; If we get here then A < 128 CMP #' ' ; If A >= ASCII " " then this is a valid alphanumerical BCS coolkey ; key press (as A is in the range 32 to 127), so jump ; down to coolkey to return this key press CMP #13 ; If A = 13 then this is the return character, so jump BEQ coolkey ; down to coolkey to return this key press CMP #21 ; If A <> 21 jump up to badkey BNE badkey .coolkey ; If we get here then the character we read is valid, so ; return it CLC ; Clear the C flag RTS ; Return from the subroutine
Name: WSCAN [Show more] Type: Subroutine Category: Drawing the screen Summary: Wait for the vertical sync
Context: See this subroutine on its own page References: This subroutine is called as follows: * DELAY calls WSCAN * DK4 calls WSCAN * TT16 calls WSCAN

Wait for vertical sync to occur on the video system - in other words, wait for the screen to start its refresh cycle, which it does 50 times a second (50Hz) on PAL systems, or 60 times a second (60Hz) on NTSC systems. We do this by monitoring the value of RASTCT, which is updated by the interrupt routine at COMIRQ1 as it draws the two different parts of the screen (the upper part containing the space view, and the lower part containing the dashboard).
.WSCAN PHA ; Store A on the stack so we can preserve it .WSC1 LDA RASTCT ; Wait until RASTCT is non-zero, which indicates that BEQ WSC1 ; the VIC-II is now drawing the dashboard .WSC2 LDA RASTCT ; Wait until RASTCT is zero, which indicates that the BNE WSC2 ; VIC-II is now drawing the top line of the visible ; screen PLA ; Restore A from the stack so it is unchanged RTS ; Return from the subroutine
Name: CHPR2 [Show more] Type: Subroutine Category: Text Summary: Character print vector handler
Context: See this subroutine on its own page References: This subroutine is called as follows: * COLD calls CHPR2

This routine is set as the handler in CHRV, so it replaces the Kernal's character-printing routine.
Arguments: A The character to print
Returns: C flag The C flag is cleared
.CHPR2 CMP #123 ; If the character to print in A is outside of the range BCS whosentthisshit ; 13 to 122, jump to whosentthisshit to print nothing CMP #13 BCC whosentthisshit BNE CHPR ; If A is not 13, jump to CHPR to print the character, ; returning from the subroutine using a tail call LDA #12 ; If we get here then A is 13, so call CHPR with A = 12, JSR CHPR ; which will print a carriage return LDA #13 ; Set A = 13 so it is unchanged .whosentthisshit CLC ; Clear the C flag, as the CHPR routine does this and ; we need CHPR2 to act in the same way RTS ; Return from the subroutine
Name: R5 [Show more] Type: Subroutine Category: Text Summary: Make a beep and jump back into the character-printing routine at CHPR
Context: See this subroutine on its own page References: This subroutine is called as follows: * CHPR calls R5
.R5 JSR BEEP ; Call the BEEP subroutine to make a short, high beep JMP RR4 ; Jump to RR4 to restore the registers and return from ; the subroutine using a tail call
Name: clss [Show more] Type: Subroutine Category: Drawing the screen Summary: Clear the screen, move the text cursor to the top-left corner and jump back into the CHPR routine to print the next character
Context: See this subroutine on its own page References: This subroutine is called as follows: * CHPR calls clss
.clss JSR TT66simp ; Call TT66simp to clear the whole screen inside the box ; border, and move the text cursor to the top-left ; corner LDA K3 ; We called this routine from CHPR, which put the ; character we are printing into K3, so set A to the ; character number so we can jump back to CHPR to print ; it on the newly cleared screen JMP RRafter ; Jump back into the CHPR routine to print the character ; in A
Name: RR4S [Show more] Type: Subroutine Category: Text Summary: A jump point that restores the registers and returns from the CHPR subroutine (so we can use a branch instruction to jump to RR4)
Context: See this subroutine on its own page References: This subroutine is called as follows: * CHPR calls RR4S
.RR4S JMP RR4 ; Jump to RR4 to restore the registers and return from ; the subroutine using a tail call (this JMP enables us ; to jump to RR4 using a branch to RR4S though this ; isn't actually done anywhere)
Name: TT67X [Show more] Type: Subroutine Category: Text Summary: Print a newline
Context: See this subroutine on its own page References: This subroutine is called as follows: * STATUS calls TT67X
.TT67X ; This does the same as the existing TT67 routine, which ; is also present in this source, so it isn't clear why ; this duplicate exists ; ; In the original source, this version also has the name ; TT67, but because BeebAsm doesn't allow us to redefine ; labels, this one has been renamed TT67X LDA #12 ; Set A to a carriage return character ; Fall through into CHPR to print the newline
Name: CHPR [Show more] Type: Subroutine Category: Text Summary: Print a character at the text cursor by poking into screen memory Deep dive: Drawing text
Context: See this subroutine on its own page References: This subroutine is called as follows: * BELL calls CHPR * BRBR calls CHPR * CHPR2 calls CHPR * GTDRV calls CHPR * MT26 calls CHPR * TITLE calls CHPR * TT26 calls CHPR * R5 calls via RR4 * RR4S calls via RR4 * clss calls via RRafter

Print a character at the text cursor (XC, YC), do a beep, print a newline, or delete left (backspace). The CHPR2 sends characters here for printing if they are in the range 13-122.
Arguments: A The character to be printed. Can be one of the following: * 7 (beep) * 10 (line feed) * 11 (clear the top part of the screen and draw a border) * 12-13 (carriage return) * 32-95 (ASCII capital letters, numbers and punctuation) * 127 (delete the character to the left of the text cursor and move the cursor to the left) XC Contains the text column to print at (the x-coordinate) YC Contains the line number to print on (the y-coordinate)
Returns: A A is preserved X X is preserved Y Y is preserved C flag The C flag is cleared
Other entry points: RR4 Restore the registers and return from the subroutine RRafter A re-entry point from the clss routine to print the character in A
.CHPR STA K3 ; Store the A, X and Y registers, so we can restore STY YSAV2 ; them at the end (so they don't get changed by this STX XSAV2 ; routine) LDY QQ17 ; Load the QQ17 flag, which contains the text printing ; flags CPY #255 ; If QQ17 = 255 then printing is disabled, so jump to BEQ RR4S ; RR4 (via the JMP in RR4S) to restore the registers ; and return from the subroutine using a tail call .RRafter CMP #7 ; If this is a beep character (A = 7), jump to R5, BEQ R5 ; which will emit the beep, restore the registers and ; return from the subroutine CMP #32 ; If this is an ASCII character (A >= 32), jump to RR1 BCS RR1 ; below, which will print the character, restore the ; registers and return from the subroutine CMP #10 ; If this is control code 10 (line feed) then jump to BEQ RRX1 ; RRX1, which will move down a line, restore the ; registers and return from the subroutine .RRX2 LDX #1 ; If we get here, then this is control code 12 or 13, STX XC ; both of which are used. This code prints a newline, ; which we can achieve by moving the text cursor ; to the start of the line (carriage return) and down ; one line (line feed). These two lines do the first ; bit by setting XC = 1, and we then fall through into ; the line feed routine that's used by control code 10 .RRX1 CMP #13 ; If this is control code 13 (carriage return) then jump BEQ RR4S ; to RR4 (via the JMP in RR4S) to restore the registers ; and return from the subroutine using a tail call INC YC ; Increment the text cursor y-coordinate to move it ; down one row BNE RR4S ; Jump to RR4 via RR4S to restore the registers and ; return from the subroutine using a tail call .RR1 ; If we get here, then the character to print is an ; ASCII character in the range 32-95. The quickest way ; to display text on-screen is to poke the character ; pixel by pixel, directly into screen memory, so ; that's what the rest of this routine does ; ; The first step, then, is to get hold of the bitmap ; definition for the character we want to draw on the ; screen (i.e. we need the pixel shape of this ; character) ; ; The Commodore 64 version of Elite uses the same ; character bitmaps as the BBC Micro version of Elite, ; which in turn uses the characters from the BBC Micro's ; MOS operating system ; ; A copy of these bitmap definitions is embedded into ; this source code at page FONT, so page 0 of the font ; is at FONT, page 1 is at FONT+1, and page 2 at ; FONT+3 ; ; There are definitions for 32 characters in each of the ; three pages of MOS memory, as each definition takes up ; 8 bytes (8 rows of 8 pixels) and 32 * 8 = 256 bytes = ; 1 page. So: ; ; ASCII 32-63 are defined in $C000-$C0FF (page 0) ; ASCII 64-95 are defined in $C100-$C1FF (page 1) ; ASCII 96-126 are defined in $C200-$C2F0 (page 2) ; ; The following code reads the relevant character ; bitmap from the copied MOS bitmaps at FONT and pokes ; those values into the correct position in screen ; memory, thus printing the character on-screen ; ; It's a long way from 10 PRINT "Hello world!":GOTO 10 TAY ; Copy the character number from A to Y, as we are ; about to pull A apart to work out where this ; character definition lives in memory ; Now we want to set X to point to the relevant page ; number for this character - i.e. FONT to FONT+2 ; The following logic is easier to follow if we look ; at the three character number ranges in binary: ; ; Bit # 76543210 ; ; 32 = %00100000 Page 0 of bitmap definitions ; 63 = %00111111 ; ; 64 = %01000000 Page 1 of bitmap definitions ; 95 = %01011111 ; ; 96 = %01100000 Page 2 of bitmap definitions ; 125 = %01111101 ; ; We'll refer to this below LDX #HI(FONT)-1 ; Set X to point to the page before the first font page, ; which is HI(FONT) - 1 ASL A ; If bit 6 of the character is clear (A is 32-63) ASL A ; then skip the following instruction BCC P%+4 LDX #HI(FONT)+1 ; A is 64-126, so set X to point to the after the first ; font page, which is HI(FONT) + 1 ASL A ; If bit 5 of the character is clear (A is 64-95) BCC P%+3 ; then skip the following instruction INX ; Increment X ; ; By this point, we started with X = FONT%-1, and then ; we did the following: ; ; If A = 32-63: skip then INX so X = FONT ; If A = 64-95: X = FONT+1 then skip so X = FONT+1 ; If A = 96-126: X = FONT+1 then INX so X = FONT+2 ; ; In other words, X points to the relevant page. But ; what about the value of A? That gets shifted to the ; left three times during the above code, which ; multiplies the number by 8 but also drops bits 7, 6 ; and 5 in the process. Look at the above binary ; figures and you can see that if we cleared bits 5-7, ; then that would change 32-53 to 0-31... but it would ; do exactly the same to 64-95 and 96-125. And because ; we also multiply this figure by 8, A now points to ; the start of the character's definition within its ; page (because there are 8 bytes per character ; definition) ; ; Or, to put it another way, X contains the high byte ; (the page) of the address of the definition that we ; want, while A contains the low byte (the offset into ; the page) of the address STA P+1 ; Store the address of this character's definition in STX P+2 ; P(2 1) LDA XC ; Fetch XC, the x-coordinate (column) of the text cursor ; into A CMP #31 ; If A >= 31, i.e. the text cursor past the right edge BCS RRX2 ; the screen, jump to RRX2 to move to column 1 LDA #$80 ; Set SC to $80 so we can use it in the calculation of STA SC ; the character's screen address below LDA YC ; Fetch YC, the y-coordinate (row) of the text cursor CMP #24 ; If the text cursor is on the screen (i.e. YC < 24, so BCC RR3 ; we are on rows 0-23), then jump to RR3 to print the ; character JMP clss ; Otherwise we are off the bottom of the screen, so call ; clss to clear the screen and draw a border box, ; before jumping back to RRafter with A set to the ; character to be printed at the top of the newly ; cleared screen .RR3 ; A contains the value of YC - the screen row where we ; want to print this character - so now we need to ; convert this into a screen address, so we can poke ; the character data to the right place in screen ; memory LSR A ; Set (A SC) = (A SC) >> 2 ROR SC ; = (YC $80) / 4 LSR A ; = (YC * 256 / 4) + ($80 / 4) ROR SC ; = YC * 64 + $20 ; ; This also clears the C flag, as the low bits of SC are ; all zeroes ADC YC ; Set A = A + YC ; ; So (A SC) = (A SC) + (YC 0) ; = YC * 64 + $20 + YC * 256 ; = YC * 320 + 32 ADC #HI(SCBASE) ; The low byte of the screen bitmap address in SCBASE is STA SC+1 ; always zero, so this does the following: ; ; SC(1 0) = SCBASE + (A SC) ; = SCBASE + YC * 320 + 32 ; ; So SC(1 0) contains the screen address we want to poke ; the character into, because: ; ; * The screen bitmap starts at SCBASE ; ; * Each character row of 40 character blocks takes up ; 40 * 8 = 320 bytes, and we want to print on row ; YC, so we add YC * 320 bytes to get to the correct ; character row ; ; * Because the game screen is 256 pixels wide and the ; Commodore 64 screen is 320 pixels wide, we have a ; 32-pixel margin on each side that we need to skip ; past, and 32 pixels is the width of four character ; blocks, each of which takes up eight bytes of ; bitmap memory, so we add another 4 * 8 = 32 bytes ; to cater for the indent LDA XC ; Set SC(1 0) = SC(1 0) + XC * 8 ASL A ; ASL A ; So SC(1 0) now points to the screen address of the ASL A ; character block in column XC, which is where we want ADC SC ; to draw our character STA SC BCC P%+4 INC SC+1 CPY #127 ; If the character number (which is in Y) <> 127, then BNE RR2 ; skip to RR2 to print that character, otherwise this is ; the delete character, so continue on DEC XC ; We want to delete the character to the left of the ; text cursor and move the cursor back one, so let's ; do that by decrementing YC. Note that this doesn't ; have anything to do with the actual deletion below, ; we're just updating the cursor so it's in the right ; position following the deletion DEC SC+1 ; Decrement the high byte of the screen address to point ; to the address of the current character, minus one ; page LDY #$F8 ; Set Y = $F8, so the following call to ZESNEW will ; count Y upwards from $F8 to $FF JSR ZESNEW ; Call ZESNEW, which zero-fills from address SC(1 0) + Y ; to SC(1 0) + $FF. SC(1 0) points to the character ; above the text cursor, and adding $FF to this would ; point to the cursor, so adding $F8 points to the ; character before the cursor, which is the one we want ; to delete. So this call zero-fills the character to ; the left of the cursor, which erases it from the ; screen BEQ RR4 ; We are done deleting, so restore the registers and ; return from the subroutine (this BNE is effectively ; a JMP as ZESNEW always returns with the Z flag set) .RR2 INC XC ; Once we print the character, we want to move the text ; cursor to the right, so we do this by incrementing ; XC. Note that this doesn't have anything to do ; with the actual printing below, we're just updating ; the cursor so it's in the right position following ; the print EQUB $2C ; Skip the next instruction by turning it into ; $2C $85 $08, or BIT $0885, which does nothing apart ; from affect the flags STA SC+1 ; This instruction has no effect, as it is always ; skipped, so perhaps this was accidentally left behind ; from development LDY #7 ; We want to print the 8 bytes of character data to the ; screen (one byte per row), so set up a counter in Y ; to count these bytes .RRL1 LDA (P+1),Y ; The character definition is at P(2 1) - we set this up ; above - so load the Y-th byte from P(2 1), which will ; contain the bitmap for the Y-th row of the character EOR (SC),Y ; If we EOR this value with the existing screen ; contents, then it's reversible (so reprinting the ; same character in the same place will revert the ; screen to what it looked like before we printed ; anything); this means that printing a white pixel ; onto a white background results in a black pixel, but ; that's a small price to pay for easily erasable text STA (SC),Y ; Store the Y-th byte at the screen address for this ; character location DEY ; Decrement the loop counter BPL RRL1 ; Loop back for the next byte to print to the screen LDY YC ; Set SC(1 0) to the address of the start of the current LDA celllookl,Y ; text row in screen RAM, by looking up the address from STA SC ; the celllookl and celllookh tables for the row given LDA celllookh,Y ; in YC STA SC+1 ; ; In the text view, screen RAM is used to determine the ; colour of each on-screen character, so SC(1 0) is now ; set to the address of the colour information for the ; start of the current text row LDY XC ; Set the contents of SC(1 0) + XC to COL2 LDA COL2 ; STA (SC),Y ; This sets the XC-th byte in SC(1 0) to COL2, which ; sets the colour information for the XC-th character in ; the current text row to COL2 - in other words, this ; sets the colour of the character we just drew to COL2 .RR4 LDY YSAV2 ; We're done printing, so restore the values of the LDX XSAV2 ; A, X and Y registers that we saved above and clear LDA K3 ; the C flag, so everything is back to how it was CLC RTS ; Return from the subroutine
Name: TTX66K [Show more] Type: Subroutine Category: Drawing the screen Summary: Clear the whole screen or just the space view (as appropriate), draw a border box, and if required, show the dashboard
Context: See this subroutine on its own page References: This subroutine is called as follows: * TTX66 calls TTX66K * DEATH calls via BOX

Clear the top part of the screen (the space view) and draw a border box along the top and sides.
Other entry points: BOX Just draw the border box along the top and sides
.TTX66K ; We start by resetting screen RAM for the text view, ; which lives at $6000 and has one byte that defines the ; palette for each character block (as we want to set ; the palette to white pixels on a black background) LDA #$04 ; Set SC(1 0) = $6004 STA SC ; LDA #$60 ; So this skips the four character border on the left STA SC+1 ; of the screen, so SC(1 0) points to the top-left ; character of the text view in screen RAM LDX #24 ; The text view has 24 character rows, so set a row ; counter in X .BOL3 LDA #$10 ; Set A to a colour data byte that sets colour 1 (white) ; for the foreground and colour 0 (black) for the ; background LDY #31 ; The game screen is 32 characters wide, so set a column ; counter in Y .BOL4 STA (SC),Y ; Set the Y-th colour data byte at SC(1 0) to A, to set ; white pixels on a black background for the text view DEY ; Decrement the column counter BPL BOL4 ; Loop back until we have set colour bytes for the whole ; row LDA SC ; Set SC(1 0) = SC(1 0) + 40 CLC ; ADC #40 ; So this moves SC(1 0) to the next row of colour data, STA SC ; as there are 40 characters on each row of the screen BCC P%+4 ; (with Elite only taking up the middle 32 characters) INC SC+1 DEX ; Decrement the row counter BNE BOL3 ; Loop back until we have set colour bytes for all 24 ; rows, by which time we will have reset the colour ; data for the whole text view ; Next, we zero the space view portion of the screen ; bitmap to clear the top part of the screen of any ; graphics or border boxes LDX #HI(SCBASE) ; Set X to the page number for the start of the screen ; bitmap in memory, which is at SCBASE, so we can use ; this as a page counter while resetting the screen ; bitmap .BOL1 JSR ZES1k ; Call ZES1k to zero-fill the page in X, which will ; clear one page of the screen bitmap by setting all ; pixels to the background colour INX ; Increment the page counter in X CPX #HI(DLOC%) ; Loop back to keep clearing pages until we reach DLOC%, BNE BOL1 ; which is the address of the start of the dashboard in ; the screen bitmap, so we loop back until we have ; cleared up to the start of the page that contains the ; start of the dashboard (which is most of the space ; view, but not the very last bit ; By this point X = HI(DLOC%), which we use in a couple ; of places below LDY #LO(DLOC%)-1 ; Set Y to the low byte of the address of the byte just ; before the first dashboard byte JSR ZES2k ; Call ZES2k to zero-fill from address (X SC) + Y to ; (X SC) + 1 ; ; X is HI(DLOC%), so this zero-fills the page at DLOC% ; from offset Y down to offset 1 ; ; So this resets the rest of the space view right up ; to the start of the dashboard, though it doesn't do ; the byte at offset 0 STA (SC),Y ; The call to ZES2k returns with both A = 0 and Y = 0, ; and SC(1 0) is set to the base address of the block we ; have just zeroed, so to zero the byte at offset 0, we ; just need to set SC(1 0) to 0 LDA #1 ; Move the text cursor to column 1 STA XC STA YC ; Move the text cursor to row 1 LDA QQ11 ; If QQ11 = 0 then this is the space view, so jump to BEQ wantSTEP ; wantdials via wantSTEP to display the dashboard in ; the lower portion of the screen CMP #13 ; If QQ11 = 13 then this is the title screen, so skip BNE P%+5 ; the following instruction if this is not the title ; screen .wantSTEP JMP wantdials ; If we get here then QQ11 = 0 or 13, which is the space ; view or title screen, so jump to wantdials to display ; the dashboard ; If we get here then this is not the space view or ; title screen, so we do not display the dashboard LDA #$81 ; Set abraxas = $81, so the colour of the lower part of STA abraxas ; the screen is determined by screen RAM at $6000 ; (i.e. for when the text view is being shown) LDA #%11000000 ; Clear bit 4 of caravanserai so that the lower part of STA caravanserai ; the screen (the dashboard) is shown in standard bitmap ; mode ; We set X = HI(DLOC%) above, so it points at the page ; that contains the start of the dashboard and we can ; use this to clear the rest of the screen bitmap, as ; we stopped when we reached the dashboard portion of ; the screen (and we aren't showing the dashboard in ; this view) .BOL2 JSR ZES1k ; Call ZES1k to zero-fill the page in X, which will ; clear part of a character row INX ; Increment the page in X CPX #HI(SCBASE)+$20 ; Loop back until we have cleared all $20 pages of the BNE BOL2 ; screen bitmap (i.e. from $4000 to $5FFF) LDX #0 ; Set the compass colour in COMC to the background STX COMC ; colour, so no compass dot gets drawn STX DFLAG ; Set DFLAG to 0 to indicate that there is no dashboard ; being shown on-screen INX ; Move the text cursor to column 1 (though we already STX XC ; did this, so this isn't strictly necessary) STX YC ; Move the text cursor to row 1 (though again, we ; already did this) JSR BLUEBAND ; Clear the borders along the edges of the space view, ; to hide any sprites that might be lurking there JSR zonkscanners ; Hide all ships on the scanner JSR NOSPRITES ; Call NOSPRITES to disable all sprites and remove them ; from the screen ; We now set the colour of the top row of the screen to ; yellow on black, for the border box LDY #31 ; The border box is 32 characters wide, so set a column ; counter in Y LDA #$70 ; Set A to a colour data byte that sets colour 7 ; (yellow) for the foreground and colour 0 (black) for ; the background, so the border box gets drawn in yellow .BOL5 STA $6004,Y ; Set the colour data for the Y-th character of the top ; character row to A, skipping the first four characters ; that form the left border DEY ; Decrement the column counter in Y BPL BOL5 ; Loop back until the whole top character row is set to ; a palette of yellow on black LDX QQ11 ; If QQ11 is one of the following: CPX #2 ; BEQ BOX ; * 2 (Buy Cargo screen) CPX #64 ; BEQ BOX ; * 64 (Long-range Chart) CPX #128 ; BEQ BOX ; * 128 (Short-range Chart) ; ; then jump to BOX to skip setting the third row to ; yellow on black (as otherwise this will affect the ; colours just below the line beneath the title text) ; We now set the colour of the third row of the screen ; to yellow on black, for the line beneath the title ; text LDY #31 ; The title box is 32 characters wide, so set a column ; counter in Y .BOL6 STA $6054,Y ; Set the colour data for the Y-th character of the ; third character row to A, skipping the first four ; characters that form the left border ; ; The address breaks down as follows: ; ; $6054 = $6000 + 2 * 40 + 4 ; ; as each row on-screen contains 40 characters, and we ; want to skip the first two rows, and indent to skip ; the left screen border DEY ; Decrement the column counter in Y BPL BOL6 ; Loop back until the whole of the third character row ; is set to a palette of yellow on black .BOX LDX #199 ; Draw a horizontal line across the screen at pixel JSR BOXS ; y-coordinate 199, to draw the bottom edge of the ; border box LDA #$FF ; This draws an 8-pixel line in character column 35 on STA SCBASE+$1F1F ; character row 24, which is within the four-character ; border to the right of the game screen and just within ; the lower portion of the screen (where the dashboard ; lives) ; ; The palette for this part of the screen is black on ; black, so the result isn't visible, and it's unclear ; what this is for; perhaps it was a visual check used ; during development to ensure that the border area was ; indeed not showing any pixels ; ; This write is manually reversed in the DEATH routine LDX #25 ; Set X = 25 so when we fall into BOX2, we draw the ; left and right edges of the border box at a height of ; 25 character rows rather than 18, so the box surrounds ; the entire screen, and not just the space view portion EQUB $2C ; Skip the first instruction of BOX2 by turning it into ; $2C $A2 $12, or BIT $12A2, which does nothing apart ; from affect the flags ; Fall into BOX2 to draw the left and right edges of the ; border box for the text view
Name: BOX2 [Show more] Type: Subroutine Category: Drawing the screen Summary: Draw the left and right edges of the border box for the space view
Context: See this subroutine on its own page References: This subroutine is called as follows: * wantdials calls BOX2
.BOX2 LDX #18 ; The space view is 18 character rows tall, so set a ; row counter in X so we draw edges along the sides of ; the space view only STX T2 ; Store the value of X in T2 so we can retrieve it for ; the right edge below LDY #LO(SCBASE+3*8) ; Set (Y SC) to the address of the fourth byte in the STY SC ; screen bitmap, so we draw the border box in the LDY #HI(SCBASE+3*8) ; rightmost two pixels of the four-character screen ; border on the left LDA #%00000011 ; Set a pixel byte in A with the two rightmost pixels ; set, to use for drawing the left edge of the border ; box JSR BOXS2 ; Draw the left vertical edge of the border box LDY #LO(SCBASE+36*8) ; Set (Y SC) to the address of the first byte to the STY SC ; right of the game screen, skipping the four character LDY #HI(SCBASE+36*8) ; border on the left and the 32 characters of the game ; screen, so we draw the border box in the leftmost two ; pixels of the four-character screen border on the ; right LDA #%11000000 ; Set a pixel byte in A with the two leftmost pixels ; set, to use for drawing the right edge of the border ; box LDX T2 ; Set X to the height of the border box that we stored ; in T2 above JSR BOXS2 ; Draw the right vertical edge of the border box LDA #1 ; This draws a pixel in character column 35 on the first STA SCBASE+$118 ; character row, which is within the four-character ; border to the right of the game screen ; ; The palette for this part of the screen is black on ; black, so the result isn't visible, and it's unclear ; what this is for; perhaps it was a visual check used ; during development to ensure that the border area was ; indeed not showing any pixels ; ; This write is manually reversed in the DEATH routine LDX #0 ; Set X = 0 so we draw a horizontal line across the ; screen at pixel y-coordinate 0 ; Fall into BOXS to draw the top horizontal edge of the ; border box at y-coordinate 0
Name: BOXS [Show more] Type: Subroutine Category: Drawing the screen Summary: Draw a horizontal line across the screen at pixel y-coordinate X
Context: See this subroutine on its own page References: This subroutine is called as follows: * TTX66K calls BOXS

Arguments: X The pixel y-coordinate for the line
.BOXS STX Y1 ; Set Y1 = X LDX #0 ; Set X1 = 0 STX X1 DEX ; Set X2 = 255 STX X2 JMP HLOIN ; Call HLOIN to draw a horizontal line from (X1, Y1) to ; (X2, Y1), so that's from (0, X) to (255, X), and ; return from the subroutine using a tail call
Name: BOXS2 [Show more] Type: Subroutine Category: Drawing the screen Summary: Draw a vertical line for the left or right border box edge
Context: See this subroutine on its own page References: This subroutine is called as follows: * BOX2 calls BOXS2

Arguments: A A screen bitmap pixel byte to use for the edge (Y SC) The address in screen bitmap memory of the character block at the top of the edge X The height of the line in character blocks (so the line will be 8 * X pixels tall)
.BOXS2 STA R2 ; Store the pixel byte for the edge in R2, so we can ; fetch it in the drawing loop STY SC+1 ; Set SC(1 0) = (Y SC), so SC(1 0) points to the address ; in the screen bitmap where we start drawing the line .BOXL2 LDY #7 ; We start by drawing the vertical line in all eight ; pixel rows in the character block, so set a pixel row ; counter in Y .BOXL3 LDA R2 ; Set A to the pixel byte containing set bits in the ; correct positions for the vertical line EOR (SC),Y ; Store A into screen memory at SC(1 0), using EOR STA (SC),Y ; logic so it merges with whatever is already on-screen DEY ; Decrement the pixel row counter BPL BOXL3 ; Loop back until we have drawn a vertical line across ; the whole character block LDA SC ; We have now drawn a whole character block, so we need CLC ; to move to the character row below, so add 320 ($140) ADC #$40 ; to SC(1 0) to move down one pixel line, as there are STA SC ; 320 bytes in each character row in the screen bitmap LDA SC+1 ADC #1 STA SC+1 DEX ; Decrement the character row counter BNE BOXL2 ; Loop back until we have drawn X character blocks RTS ; Return from the subroutine
Name: wantdials [Show more] Type: Subroutine Category: Drawing the screen Summary: Show the dashboard on-screen
Context: See this subroutine on its own page References: This subroutine is called as follows: * TTX66K calls wantdials
.wantdials JSR BOX2 ; Draw a border box around the space view LDA #$91 ; Set abraxas = $91, so the colour of the lower part of STA abraxas ; the screen is determined by screen RAM at $6400 ; (i.e. for when the dashboard is being shown) LDA #%11010000 ; Set bit 4 of caravanserai so that the lower part of STA caravanserai ; the screen (the dashboard) is shown in multicolour ; bitmap mode LDA DFLAG ; If DFLAG is non-zero then the dashboard is already BNE nearlyxmas ; being shown on-screen, so jump to nearlyxmas to skip ; displaying the dashboard on-screen ; We now copy the dashboard bitmap the copy at DSTORE% ; into the screen bitmap, so the dashboard appears ; on-screen ; ; The bitmap is seven character rows in size, which is ; 7 * 40 * 7 = $8C0 bytes, so we need to copy this many ; bytes from DSTORE% to the screen bitmap address of the ; dashboard at DLOC% LDX #8 ; Set X = 8 so we copy the first eight pages of the ; dashboard bitmap from DSTORE% to screen memory LDA #LO(DSTORE%) ; Set V(1 0) = DSTORE% STA V ; LDA #HI(DSTORE%) ; So V(1 0) points to the copy of the dashboard image STA V+1 ; and colour data at DSTORE% LDA #LO(DLOC%) ; Set SC(1 0) = DLOC% STA SC ; LDA #HI(DLOC%) ; So SC(1 0) points to the address in the screen bitmap STA SC+1 ; of the start of the dashboard at DLOC% JSR mvblockK ; Copy X pages from V(1 0) to SC(1 0), which copies all ; eight pages of the dashboard bitmap from the copy at ; DSTORE% into the screen bitmap ; We have copied $800 bytes, so now for the other $C0 ; bytes LDY #$C0 ; Set Y = $C0 so we copy this many bytes LDX #1 ; Set X = 1 so we copy this many bytes within just one ; page JSR mvbllop ; Copy Y bytes from V(1 0) to SC(1 0), so this copies ; the rest of the dashboard bitmap to the screen JSR zonkscanners ; Hide all ships on the scanner JSR DIALS ; Call DIALS to update the dashboard .nearlyxmas JSR BLUEBAND ; Clear the borders along the edges of the space view, ; to hide any sprites that might be lurking there JSR NOSPRITES ; Call NOSPRITES to disable all sprites and remove them ; from the screen LDA #$FF ; Set DFLAG to $FF to indicate that the dashboard is now STA DFLAG ; being shown on-screen RTS ; Return from the subroutine
Name: zonkscanners [Show more] Type: Subroutine Category: Drawing the screen Summary: Hide all ships on the scanner
Context: See this subroutine on its own page References: This subroutine is called as follows: * TTX66K calls zonkscanners * wantdials calls zonkscanners
.zonkscanners LDX #0 ; Set up a counter in X to work our way through all the ; ship slots in FRIN .zonkL LDA FRIN,X ; Fetch the ship type in slot X BEQ zonk1 ; If the slot contains 0 then it is empty and we have ; checked all the slots (as they are always shuffled ; down in the main loop to close up and gaps), so jump ; to zonk1 as we are done BMI zonk2 ; If the slot contains a ship type with bit 7 set, then ; it contains the planet or the sun, so jump down to ; zonk2 to skip this slot, as the planet and sun don't ; appear on the scanner JSR GINF ; Call GINF to get the address of the data block for ; ship slot X and store it in INF LDY #31 ; Clear bit 4 in the ship's byte #31, which hides it LDA (INF),Y ; from the scanner AND #%11101111 STA (INF),Y .zonk2 INX ; Increment X to point to the next ship slot BNE zonkL ; Loop back up to process the next slot (this BNE is ; effectively a JMP as X will never be zero) .zonk1 RTS ; Return from the subroutine
Name: BLUEBAND [Show more] Type: Subroutine Category: Drawing the screen Summary: Clear two four-character borders along each side of the space view
Context: See this subroutine on its own page References: This subroutine is called as follows: * TTX66K calls BLUEBAND * wantdials calls BLUEBAND

The Elite game screen is 256 pixels wide but the Commodore 64 screen is 320 pixels wide, which leaves 64 pixels (eight character blocks). We therefore show the game in the middle of the screen, and clear a four-character border along the left and right edges of the space view. This prevents graphics from spilling out of the sides of the space view (in particular the Trumble and explosion sprites).
.BLUEBAND LDX #LO(SCBASE) ; Set (Y X) = SCBASE so it contains the address of the LDY #HI(SCBASE) ; top-left corner of the four-character border along ; the left edge of the screen JSR BLUEBANDS ; Call BLUEBANDS to clear the left border LDX #LO(SCBASE+37*8) ; Set (Y X) = SCBASE so it contains the address of LDY #HI(SCBASE+37*8) ; character block 37 on the top row of the screen, which ; is the top-left corner of the border along the right ; edge of the screen (as there are four blocks for the ; left border and 32 blocks for the space view) ; Fall through into BLUEBANDS to clear the right border
Name: BLUEBANDS [Show more] Type: Subroutine Category: Drawing the screen Summary: Clear a four-character border along one side of the space view
Context: See this subroutine on its own page References: This subroutine is called as follows: * BLUEBAND calls BLUEBANDS

Arguments: (Y X) The address of the top-left corner of the border strip to fill
.BLUEBANDS STX SC ; Set SC(1 0) = (Y X) STY SC+1 LDX #18 ; The space view is 144 pixels high, which is 18 ; character rows of eight pixels each, so set a row ; counter in X .BLUEL2 LDY #23 ; The border is 24 pixels wide (four characters of ; eight pixels each), so set a pixel byte counter in Y ; to cover a whole character row of 24 pixels .BLUEL1 LDA #%11111111 ; Set A to a pixel byte with every pixel in colour 1 ; ; Colour 1 is mapped to black, so this blanks the sides ; of the screen, and because it is a non-zero colour, it ; will cover over any sprites in the border that are set ; to appear behind the screen contents ; ; The explosion sprite is the only sprite to be ; configured this way ; ; As this process is only done when we change views, it ; means changing the screen won't leave any remnants of ; the explosion sprite behind in the screen border area STA (SC),Y ; Store the pixel byte in the Y-th byte of SC(1 0) DEY ; Decrement the pixel byte counter BPL BLUEL1 ; Loop back until we have done a whole character row ; We now need to move down into the character row below, ; and each 40-character row in screen memory takes up ; 40 * 8 = 320 bytes ($140), so that's what we need to ; add to SC(1 0) LDA SC ; Set SC(1 0) = SC(1 0) + $140 CLC ; ADC #$40 ; Starting with the low bytes STA SC LDA SC+1 ; And then adding the high bytes ADC #$01 STA SC+1 DEX ; Decrement the row counter in X BNE BLUEL2 ; Loop back until we have filled all 18 rows along the ; edges of the space view RTS ; Return from the subroutine
Name: TT66simp [Show more] Type: Subroutine Category: Drawing the screen Summary: Clear the whole screen inside the border box, and move the text cursor to the top-left corner
Context: See this subroutine on its own page References: This subroutine is called as follows: * clss calls TT66simp
.TT66simp LDX #8 ; We are going to clear character rows 1 through 23, ; so that's from pixel y-coordinate 8 onwards, so set a ; set a pixel y-coordinate counter in X LDY #0 ; Set Y = 0, so we can use it as a byte counter below CLC ; Clear the C flag so the addition below works .T6SL1 LDA ylookupl,X ; Set SC(1 0) to the address in screen memory of the STA SC ; start of the character row within the game screen that LDA ylookuph,X ; contains pixel y-coordinate Y STA SC+1 TYA ; Set A = 0, which we can use to zero screen memory ; We now zero a whole page of memory (256 bytes) at ; SC(1 0), using Y as a byte counter, starting from ; Y = 0 .T6SL2 STA (SC),Y ; Zero the Y-th byte of SC(1 0) DEY ; Decrement the byte counter BNE T6SL2 ; Loop back until we have zeroed a whole page of bytes ; (which corresponds to an entire character row of width ; 256 pixels, which is the width of the game screen) TXA ; Set X = X + 8 ADC #8 ; TAX ; So X now points to the pixel coordinate at the start ; of the next character row CMP #24*8 ; Loop back until we have cleared character rows 1 BCC T6SL1 ; through 23 (i.e. values of X from 8 to 23*8) INY ; Move the text cursor to column 1 STY XC STY YC ; Move the text cursor to row 1 RTS ; Return from the subroutine
Name: ZES1k [Show more] Type: Subroutine Category: Utility routines Summary: Zero-fill the page whose number is in X
Context: See this subroutine on its own page References: This subroutine is called as follows: * TTX66K calls ZES1k

Arguments: X The page we want to zero-fill
.ZES1k LDY #0 ; If we set Y = SC = 0 and fall through into ZESNEW STY SC ; below, then we will zero-fill 255 bytes starting from ; SC - in other words, we will zero-fill the whole of ; page X
Name: ZES2k [Show more] Type: Subroutine Category: Utility routines Summary: Zero-fill a specific page
Context: See this subroutine on its own page References: This subroutine is called as follows: * TTX66K calls ZES2k

Zero-fill from address (X SC) + Y to (X SC) + 1.
Arguments: Y The offset from (X SC) where we start zeroing, counting down to 1; if Y = 0, then the whole page is reset
Returns: Z flag Z flag is set A A is 0 Y Y is 0
.ZES2k LDA #0 ; Load A with the byte we want to fill the memory block ; with - i.e. zero STX SC+1 ; We want to zero-fill page X, so store this in the ; high byte of SC, so the 16-bit address in SC and ; SC+1 is now pointing to the SC-th byte of page X .ZEL1k STA (SC),Y ; Zero the Y-th byte of the block pointed to by SC, ; so that's effectively the Y-th byte before SC DEY ; Decrement the loop counter BNE ZEL1k ; Loop back to zero the next byte RTS ; Return from the subroutine
Name: ZESNEW [Show more] Type: Subroutine Category: Utility routines Summary: Zero-fill memory from SC(1 0) to the end of the page
Context: See this subroutine on its own page References: This subroutine is called as follows: * CHPR calls ZESNEW

Zero-fill from address SC(1 0) + Y to SC(1 0) + $FF.
Arguments: Y The offset from SC(1 0) where we start zeroing, counting up to $FF SC(1 0) The starting address of the zero-fill
Returns: Z flag Z flag is set
.ZESNEW LDA #0 ; Load A with the byte we want to fill the memory block ; with - i.e. zero .ZESNEWL STA (SC),Y ; Zero the Y-th byte of the block pointed to by SC INY ; Increment the loop counter BNE ZESNEWL ; Loop back to zero the next byte RTS ; Return from the subroutine
Name: SETXC [Show more] Type: Subroutine Category: Text Summary: An unused routine to move the text cursor to a specific column
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

Arguments: A The text column
.SETXC STA XC ; Store the new text column in XC ;JMP PUTBACK ; This instruction is commented out in the original ; source RTS ; Return from the subroutine
Name: SETYC [Show more] Type: Subroutine Category: Text Summary: An unused routine to move the text cursor to a specific row
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

Arguments: A The text row
.SETYC STA YC ; Store the new text row in YC ;JMP PUTBACK ; This instruction is commented out in the original ; source RTS ; Return from the subroutine
Name: mvblockK [Show more] Type: Subroutine Category: Utility routines Summary: Copy a specific number of pages in memory
Context: See this subroutine on its own page References: This subroutine is called as follows: * wantdials calls mvblockK * wantdials calls via mvbllop

Arguments: V(1 0) Source address SC(1 0) Destination address X Number of pages of memory to copy
Other entry points: mvbllop Only copy Y bytes, rather than a whole page
.mvblockK LDY #0 ; Set an index counter in Y .mvbllop LDA (V),Y ; Copy the Y-th byte from V(1 0) to SC(1 0) STA (SC),Y DEY ; Decrement the index counter BNE mvbllop ; Loop back until we have copied a whole page of bytes INC V+1 ; Increment the high bytes of V(1 0) and SC(1 0) to INC SC+1 ; point to the next page in memory DEX ; Decrement the page counter BNE mvbllop ; Loop back until we have copied X pages of memory RTS ; Return from the subroutine
Name: CLYNS [Show more] Type: Subroutine Category: Drawing the screen Summary: Clear the bottom three text rows of the space view
Context: See this subroutine on its own page References: This subroutine is called as follows: * dockEd calls CLYNS * EQSHP calls CLYNS * hm calls CLYNS * JMTB calls CLYNS * me2 calls CLYNS * MESS calls CLYNS * qv calls CLYNS * TT219 calls CLYNS

This routine clears some space at the bottom of the screen and moves the text cursor to column 1, row 21.
.CLYNS LDA #0 ; Set the delay in DLY to 0, to indicate that we are STA DLY ; no longer showing an in-flight message, so any new ; in-flight messages will be shown instantly STA de ; Clear de, the flag that appends " DESTROYED" to the ; end of the next text token, so that it doesn't .CLYNS2 LDA #%11111111 ; Set DTW2 = %11111111 to denote that we are not STA DTW2 ; currently printing a word LDA #%10000000 ; Set bit 7 of QQ17 to switch standard tokens to STA QQ17 ; Sentence Case LDA #21 ; Move the text cursor to row 21, near the bottom of STA YC ; the screen LDA #1 ; Move the text cursor to column 1 STA XC LDA #HI(SCBASE)+$1A ; Set the high byte of SC(1 0) to SCBASE + $1A and the STA SC+1 ; low byte to $60 LDA #$60 ; STA SC ; We know that the low byte of SCBASE is zero, so this ; sets SC(1 0) as follows: ; ; SC(1 0) = SCBASE + $1A00 + $60 ; ; Each character row in the screen bitmap is 40 ; characters wide, and each character takes up 8 bytes, ; so 21 rows takes up 21 * 40 * 8 = 6720 = $1A40 bytes, ; and the first four characters of each character row ; are the blank screen margin either side of the game ; screen (and 4 * 8 = 32 = $20), so $1A60 is the screen ; bitmap address of the start of character row 22 within ; the game area, which is where we want our three blank ; rows to appear ; ; In other words, we need to blank screen memory from ; SC(1 0) onwards, for three character rows LDX #3 ; We want to clear three text rows, so set a counter in ; X for 3 rows .CLYLOOP2 LDA #0 ; Set A = 0, which we can use to zero screen memory TAY ; Set Y = 0, so we can use it as a byte counter .CLYLOOP STA (SC),Y ; Zero the Y-th byte of SC(1 0) DEY ; Decrement the byte counter BNE CLYLOOP ; Loop back until we have zeroed a whole page of bytes ; (which corresponds to an entire character row of width ; 256 pixels, which is the width of the game screen) CLC ; We have now blanked a whole text row, so we need to LDA SC ; move to the character row below, so add 320 ($140) ADC #$40 ; to SC(1 0) to move down one pixel line, as there are STA SC ; 320 bytes in each character row in the screen bitmap LDA SC+1 ADC #1 STA SC+1 DEX ; Decrement the row counter in X BNE CLYLOOP2 ; Loop back to blank another row, until we have done the ; number of rows in X ; Fall through into SCAN to return from the subroutine ; (as the first instruction of SCAN is an RTS)
Name: SCAN [Show more] Type: Subroutine Category: Dashboard Summary: Display the current ship on the scanner Deep dive: The 3D scanner
Context: See this subroutine on its own page References: This subroutine is called as follows: * ESCAPE calls SCAN * Main flight loop (Part 11 of 16) calls SCAN * MVEIT (Part 2 of 9) calls SCAN * MVEIT (Part 9 of 9) calls SCAN * WPSHPS calls SCAN

This is used both to display a ship on the scanner, and to erase it again.
Arguments: INWK The ship's data block
.SCR1 RTS ; Return from the subroutine .SCAN LDA QQ11 ; If QQ11 is non-zero then this is not the space view BNE SCR1 ; and there is no dashboard on-screen, so jump to SCR1 ; to return from the subroutine LDA INWK+31 ; Fetch the ship's scanner flag from byte #31 AND #%00010000 ; If bit 4 is clear then the ship should not be shown BEQ SCR1 ; on the scanner, so return from the subroutine (as SCR1 ; contains an RTS) LDX TYPE ; Fetch the ship's type from TYPE into X BMI SCR1 ; If this is the planet or the sun, then the type will ; have bit 7 set and we don't want to display it on the ; scanner, so return from the subroutine (as SCR1 ; contains an RTS) LDA scacol,X ; Set A to the scanner colour for this ship type from ; the X-th entry in the scacol table STA COL ; Store the scanner colour in COL so it can be used to ; draw this ship in the correct colour LDA INWK+1 ; If any of x_hi, y_hi and z_hi have a 1 in bit 6 or 7, ORA INWK+4 ; then the ship is too far away to be shown on the ORA INWK+7 ; scanner, so return from the subroutine (as SCR1 AND #%11000000 ; contains an RTS) BNE SCR1 ; If we get here, we know x_hi, y_hi and z_hi are all ; 63 (%00111111) or less ; Now, we convert the x_hi coordinate of the ship into ; the screen x-coordinate of the dot on the scanner, ; using the following (see the deep dive on "The 3D ; scanner" for an explanation): ; ; X1 = 123 + (x_sign x_hi) LDA INWK+1 ; Set A = x_hi CLC ; Clear the C flag so we can do addition below LDX INWK+2 ; Set X = x_sign BPL SC2 ; If x_sign is positive, skip the following EOR #%11111111 ; x_sign is negative, so flip the bits in A and add 1 ADC #1 ; to make it a negative number (bit 7 will now be set ; as we confirmed above that bits 6 and 7 are clear). So ; this gives A the sign of x_sign and gives it a value ; range of -63 (%11000001) to 0 .SC2 ADC #123 ; Set X1 = 123 + (x_sign x_hi) STA X1 ; Next, we convert the z_hi coordinate of the ship into ; the y-coordinate of the base of the ship's stick, ; like this (see the deep dive on "The 3D scanner" for ; an explanation): ; ; SC = 220 - (z_sign z_hi) / 4 ; ; though the following code actually does it like this: ; ; SC = 255 - (35 + z_hi / 4) LDA INWK+7 ; Set A = z_hi / 4 LSR A ; LSR A ; So A is in the range 0-15 CLC ; Clear the C flag for the addition below LDX INWK+8 ; Set X = z_sign BPL SC3 ; If z_sign is positive, skip the following EOR #%11111111 ; z_sign is negative, so flip the bits in A and set the SEC ; C flag. As above, this makes A negative, this time ; with a range of -16 (%11110000) to -1 (%11111111). And ; as we are about to do an ADC, the SEC effectively adds ; another 1 to that value, giving a range of -15 to 0 .SC3 ADC #83 ; Set A = 83 + A to give a number in the range 48 to 98 EOR #%11111111 ; Flip all the bits and store in Y2, so Y2 is in the STA SC ; range 157 to 207, with a higher z_hi giving a lower Y2 ; Now for the stick height, which we calculate using the ; following (see the deep dive on "The 3D scanner" for ; an explanation): ; ; A = - (y_sign y_hi) / 2 LDA INWK+4 ; Set A = y_hi / 2 LSR A CLC ; Clear the C flag LDX INWK+5 ; Set X = y_sign BMI SCD6 ; If y_sign is negative, skip the following, as we ; already have a positive value in A EOR #%11111111 ; y_sign is positive, so flip the bits in A and set the SEC ; C flag. This makes A negative, and as we are about to ; do an ADC below, the SEC effectively adds another 1 to ; that value to implement two's complement negation, so ; we don't need to add another 1 here .SCD6 ; We now have all the information we need to draw this ; ship on the scanner, namely: ; ; X1 = the screen x-coordinate of the ship's dot ; ; SC = the screen y-coordinate of the base of the ; stick ; ; A = the screen height of the ship's stick, with the ; correct sign for adding to the base of the stick ; to get the dot's y-coordinate ; ; First, though, we have to make sure the dot is inside ; the dashboard, by moving it if necessary ADC SC ; Set A = SC + A, so A now contains the y-coordinate of ; the end of the stick, plus the length of the stick, to ; give us the screen y-coordinate of the dot ;BPL ld246 ; This instruction is commented out in the original ; source CMP #146 ; If A >= 146, skip the following instruction, as 146 is BCS P%+4 ; the minimum allowed value of A LDA #146 ; A < 146, so set A to 146, the minimum allowed value ; for the y-coordinate of our ship's dot CMP #199 ; If A < 199, skip the following instruction, as 198 is BCC P%+4 ; the maximum allowed value of A .ld246 LDA #198 ; A >= 199, so set A to 198, the maximum allowed value ; for the y-coordinate of our ship's dot STA Y1 ; Store A in Y1, as it now contains the screen ; y-coordinate for the ship's dot, clipped so that it ; fits within the dashboard SEC ; Set A = A - SC to get the stick length, by reversing SBC SC ; the ADC SC we did above. This clears the C flag if the ; result is negative (i.e. the stick length is negative) ; and sets it if the result is positive (i.e. the stick ; length is negative) ; So now we have the following: ; ; X1 = the screen x-coordinate of the ship's dot, ; clipped to fit into the dashboard ; ; Y1 = the screen y-coordinate of the ship's dot, ; clipped to fit into the dashboard ; ; SC = the screen y-coordinate of the base of the ; stick ; ; A = the screen height of the ship's stick, with the ; correct sign for adding to the base of the stick ; to get the dot's y-coordinate ; ; C = 0 if A is negative, 1 if A is positive ; ; and we can get on with drawing the dot and stick PHP ; Store the flags (specifically the C flag) from the ; above subtraction ;BCS SC48 ; These instructions are commented out in the original ;EOR #$FF ; source. They would negate A if the C flag were set, ;ADC #1 ; which would reverse the direction of all the sticks, ; so you could turn your joystick around. Perhaps one of ; the authors' test sticks were easier to use upside ; down? Who knows... .SC48 PHA ; Store the stick height in A on the stack JSR CPIX4 ; Draw a double-height dot at (X1, Y1). This also leaves ; the following variables set up for the dot's top-right ; pixel, the last pixel to be drawn (as the dot gets ; drawn from the bottom up): ; ; SC(1 0) = screen address of the pixel's character ; block ; ; Y = number of the character row containing the pixel ; ; X = the pixel's number (0-3) in that row ; ; We can use there as the starting point for drawing the ; stick, if there is one LDA CTWOS2+2,X ; Load the same bitmap 1-pixel byte that we just used AND COL ; for the top-right pixel, and mask it with the same STA X1 ; colour, storing the result in X1, so we can use it as ; the character row byte for the stick PLA ; Restore the stick height from the stack into A PLP ; Restore the flags from above, so the C flag once again ; reflects the sign of the stick height TAX ; Copy the stick height into X BEQ RTS ; If the stick height is zero, then there is no stick to ; draw, so return from the subroutine (as RTS contains ; an RTS) BCC VL3 ; If the C flag is clear then the stick height in A is ; negative, so jump down to VL3 .VLL1 ; If we get here then the stick length is positive (so ; the dot is below the ellipse and the stick is above ; the dot, and we need to draw the stick upwards from ; the dot) DEY ; We want to draw the stick upwards, so decrement the ; pixel row in Y BPL VL1 ; If Y is still positive then it correctly points at the ; line above, so jump to VL1 to skip the following LDY #7 ; We just decremented Y up through the top of the ; character block, so we need to move it to the last row ; in the character above, so set Y to 7, the number of ; the last row ; We now need to move up into the character block above, ; and each character row in screen memory takes up $140 ; bytes ($100 for the visible part and $20 for each of ; the blank borders on the side of the screen), so ; that's what we need to subtract from SC(1 0) LDA SC ; Set SC(1 0) = SC(1 0) - $140 SEC ; SBC #$40 ; Starting with the low bytes STA SC LDA SC+1 ; And then subtracting the high bytes SBC #$01 STA SC+1 .VL1 LDA X1 ; Set A to the character row byte for the stick, which ; we stored in X1 above, and which has the same pixel ; pattern as the bottom-right pixel of the dot (so the ; stick comes out of the right side of the dot) EOR (SC),Y ; Draw the stick on row Y of the character block using STA (SC),Y ; EOR logic DEX ; Decrement the (positive) stick height in X BNE VLL1 ; If we still have more stick to draw, jump up to VLL1 ; to draw the next pixel .RTS RTS ; Return from the subroutine ; If we get here then the stick length is negative (so ; the dot is above the ellipse and the stick is below ; the dot, and we need to draw the stick downwards from ; the dot) .VL3 INY ; We want to draw the stick downwards, so we first ; increment the row counter so that it's pointing to the ; bottom-right pixel in the dot (as opposed to the top- ; right pixel that the call to CPIX4 finished on) CPY #8 ; If the row number in Y is less than 8, then it BNE VLL2 ; correctly points at the next line down, so jump to ; VLL2 to skip the following LDY #0 ; We just incremented Y down through the bottom of the ; character block, so we need to move it to the first ; row in the character below, so set Y to 0, the number ; of the first row LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each character LDA SC+1 ; row in the screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BNE, so we only need to add $13F to get the result .VLL2 INY ; We want to draw the stick itself, heading downwards, ; so increment the pixel row in Y CPY #8 ; If the row number in Y is less than 8, then it BNE VL2 ; correctly points at the next line down, so jump to ; VL2 to skip the following LDY #0 ; We just incremented Y down through the bottom of the ; character block, so we need to move it to the first ; row in the character below, so set Y to 0, the number ; of the first row LDA SC ; Otherwise we need to move up into the character block ADC #$3F ; below, so add 320 ($140) to SC(1 0) to move down one STA SC ; pixel line, as there are 320 bytes in each character LDA SC+1 ; row in the screen bitmap ADC #1 ; STA SC+1 ; We know the C flag is set as we just passed through a ; BNE, so we only need to add $13F to get the result .VL2 LDA X1 ; Set A to the character row byte for the stick, which ; we stored in X1 above, and which has the same pixel ; pattern as the bottom-right pixel of the dot (so the ; stick comes out of the right side of the dot) EOR (SC),Y ; Draw the stick on row Y of the character block using STA (SC),Y ; EOR logic INX ; Increment the (negative) stick height in X BNE VLL2 ; If we still have more stick to draw, jump up to VLL2 ; to draw the next pixel RTS ; Return from the subroutine
Save ELTJ.bin
PRINT "ELITE J" PRINT "Assembled at ", ~CODE_J% PRINT "Ends at ", ~P% PRINT "Code size is ", ~(P% - CODE_J%) PRINT "Execute at ", ~LOAD% PRINT "Reload at ", ~LOAD_J% PRINT "S.ELTJ ", ~CODE_J%, " ", ~P%, " ", ~LOAD%, " ", ~LOAD_J% SAVE "3-assembled-output/ELTJ.bin", CODE_J%, P%, LOAD%