Mucking about with 3D

The place for codemasters or beginners to talk about programming any language for the Spectrum.
Post Reply
User avatar
MonkZy
Manic Miner
Posts: 279
Joined: Thu Feb 08, 2018 1:01 pm

Mucking about with 3D

Post by MonkZy »

I really wanted to write some code to draw a simple wireframe 3D cube. After some googling around I found an article with some simple-ish code for doing just that.

https://www.twobitarcade.net/article/3d ... thon-oled/

The code was in Python so I had to de-object-ificate it. It was not too bad going converting it to BASIC. The frame rate is a tad slow.

There is an unused function for converting degrees to radians, like the code in the article. I switched to using radians in the end. The code is a bit messy but it works. I guess it should be easy to alter the number of points, the vertices and edges to create different objects. Best run in an emulator with the speed cranked up to max.

Code: Select all

100 DEF FN r(d) = d * PI /180
110 DIM p(8,3) : DIM e(12,2)
115 DIM o(8,3) 
120 FOR a=1 TO 8
130 FOR b=1 TO 3
140 READ p(a,b) 
150 NEXT b
160 NEXT a
170 FOR a=1 TO 12
180 READ e(a,1),e(a,2)
190 NEXT a

200 LET w=256 : LET h=128 : LET fov=100 : LET dist=4

290 FOR a=0 TO 2*PI STEP PI/180

300 FOR v=1 TO 8
310 LET x=p(v,1)
320 LET y=p(v,2)
330 LET z=p(v,3)
340 LET rad=a
350 GO SUB 1000
351 LET x=ox :LET y=oy:LET z=oz
352 GO SUB 1100
353 LET x=ox :LET y=oy:LET z=oz
354 GO SUB 1200
359 GO SUB 1300
360 LET o(v,1)=ox
370 LET o(v,2)=oy
380 LET o(v,3)=oz
390 NEXT v

395 CLS

400 FOR v=1 TO 12
410 LET x=INT(o(e(v,1),1))
420 LET y=INT(o(e(v,1),2))
430 LET x2=INT(o(e(v,2),1))
440 LET y2=INT(o(e(v,2),2))
450 PLOT x,y
460 DRAW x2-x,y2-y
470 NEXT v

480 NEXT a

490 GO TO 290

999 STOP

1000 REM rotateX 
1020 LET cosa = COS (rad)
1030 LET sina = SIN (rad)
1040 LET oy = y * cosa - z * sina
1050 LET oz = y * sina + z * cosa
1055 LET ox = x
1060 RETURN
1100 REM rotateY
1120 LET cosa = COS (rad)
1130 LET sina = SIN (rad)
1140 LET oz = z * cosa - x * sina
1150 LET ox = z * sina + x * cosa
1155 LET oy = y
1160 RETURN
1200 REM rotateZ
1220 LET cosa = COS (rad)
1230 LET sina = SIN (rad)
1240 LET ox = x * cosa - y * sina
1250 LET oy = x * sina + y * cosa
1255 LET oz = z
1260 RETURN
1300 REM project
1305 LET fact=fov/(dist+z)
1310 LET ox=(ox*fact) + (w/2)
1320 LET oy=(-oy*fact) + (h/2)
1330 RETURN

2000 REM points
2010 DATA -1,1,-1
2020 DATA 1,1,-1
2030 DATA 1,-1,-1
2040 DATA -1,-1,-1
2050 DATA -1,1,1
2060 DATA 1,1,1
2070 DATA 1,-1,1
2080 DATA -1,-1,1

2100 REM edges
2110 DATA 1,2
2120 DATA 2,3
2130 DATA 3,4
2140 DATA 4,1
2150 DATA 6,5
2160 DATA 5,8
2170 DATA 8,7
2180 DATA 7,6
2190 DATA 1,5
2200 DATA 2,6
2210 DATA 3,7
2220 DATA 4,8
3d-cube.tap
User avatar
MonkZy
Manic Miner
Posts: 279
Joined: Thu Feb 08, 2018 1:01 pm

Re: Mucking about with 3D

Post by MonkZy »

Cleaned up the code. Properly ported the original code for the rotation increments, returned to using degrees. You now have 3 variables for the x,y,z rotation increments. Original code is by Martin Fitzpatrick,

Code: Select all


10 REM 3d-cube-rotation
20 REM original code by Martin Fitzpatrick
30 REM ported by MonkZy
40 LET w=256 : LET h=128 : LET fov=100 : LET dist=4
50 LET rotx=2 : LET roty=2 : LET rotz=2 

90 REM function and set arrays
100 DEF FN r(d) = d * PI /180
110 DIM p(8,3) : DIM e(12,2)
115 DIM o(8,3) 
120 FOR a=1 TO 8
130 FOR b=1 TO 3
140 READ p(a,b) 
150 NEXT b
160 NEXT a
170 FOR a=1 TO 12
180 READ e(a,1),e(a,2)
190 NEXT a

200 LET angx=0 : LET angy=0 : LET angz=0

290 REM calculate points
300 FOR v=1 TO 8
310 LET x=p(v,1)
320 LET y=p(v,2)
330 LET z=p(v,3)
350 GO SUB 1000
360 LET o(v,1)=ox
370 LET o(v,2)=oy
380 LET o(v,3)=oz
390 NEXT v

395 CLS

400 FOR v=1 TO 12
410 LET x=INT(o(e(v,1),1))
420 LET y=INT(o(e(v,1),2))
430 LET x2=INT(o(e(v,2),1))
440 LET y2=INT(o(e(v,2),2))
450 PLOT x,y
460 DRAW x2-x,y2-y
470 NEXT v

480 NEXT a

490 LET angx=angx+rotx
500 LET angy=angy+roty
510 LET angz=angz+rotz
520 GO TO 290

1000 REM rotateX
1010 LET rad=FN r(angx) 
1020 LET cosa = COS (rad)
1030 LET sina = SIN (rad)
1040 LET oy = y * cosa - z * sina
1050 LET oz = y * sina + z * cosa
1060 LET y=oy:LET z=oz
1100 REM rotateY
1110 LET rad=FN r(angy)
1120 LET cosa = COS (rad)
1130 LET sina = SIN (rad)
1140 LET oz = z * cosa - x * sina
1150 LET ox = z * sina + x * cosa
1160 LET z=oz:LET x=ox
1200 REM rotateZ
1210 LET rad=FN r(angz)
1220 LET cosa = COS (rad)
1230 LET sina = SIN (rad)
1240 LET ox = x * cosa - y * sina
1250 LET oy = x * sina + y * cosa
1300 REM project
1305 LET fact=fov/(dist+z)
1310 LET ox=(ox*fact) + (w/2)
1320 LET oy=(-oy*fact) + (h/2)
1330 RETURN

2000 REM points
2010 DATA -1,1,-1
2020 DATA 1,1,-1
2030 DATA 1,-1,-1
2040 DATA -1,-1,-1
2050 DATA -1,1,1
2060 DATA 1,1,1
2070 DATA 1,-1,1
2080 DATA -1,-1,1

2100 REM edges
2110 DATA 1,2
2120 DATA 2,3
2130 DATA 3,4
2140 DATA 4,1
2150 DATA 6,5
2160 DATA 5,8
2170 DATA 8,7
2180 DATA 7,6
2190 DATA 1,5
2200 DATA 2,6
2210 DATA 3,7
2220 DATA 4,8

3d-cube-1v3.tap
User avatar
djnzx48
Manic Miner
Posts: 730
Joined: Wed Dec 06, 2017 2:13 am
Location: New Zealand

Re: Mucking about with 3D

Post by djnzx48 »

Interesting. I was able to speed up the first version slightly by combining the three rotation subroutines into one, and declaring some variables at the start of the program. This was the new subroutine I used (borrowed from here):

Code: Select all

1000 REM rotate
1020 LET cosa=COS rad
1030 LET sina=SIN rad
1040 LET sinacosa=sina*cosa
1050 LET sina2=sina*sina
1055 LET cosa2=cosa*cosa
1060 LET ox=x*cosa2+y*(cosa*sina2-sinacosa)+z*(sina*cosa2+sina2)
1070 LET oy=x*sinacosa+y*(sina*sina2+cosa2)+z*(cosa*sina2-sinacosa)
1080 LET oz=-x*sina+y*sinacosa+z*cosa2
1090 RETURN
This probably wouldn't help much for the second version, assuming all the angles are different.
User avatar
MonkZy
Manic Miner
Posts: 279
Joined: Thu Feb 08, 2018 1:01 pm

Re: Mucking about with 3D

Post by MonkZy »

When I started out with the idea, I did find that wiki page. The math was way above my level of understanding and overwhelming. I am going to go back to it as I go. My long term goal is to make a short demo. My next project is to produce some z80 code that produces the same output. I am aiming to create a lookup table of SIN and COS calculations. I did glance at the ROM code for the SIN and COS commands, but backed away. I think I could get a handle on the multiplication and division needed, if I can use a lookup table. I have already found some example z80 code for the calculations (floating point and fixed point), on a programmable calculator wiki. It will be a bit of a 'Lamer Demo' project of old. I have also coded a sinus scroller, so this will be effect #2. Music will be an issue, if I get that far :D
User avatar
Ast A. Moore
Rick Dangerous
Posts: 2641
Joined: Mon Nov 13, 2017 3:16 pm

Re: Mucking about with 3D

Post by Ast A. Moore »

MonkZy wrote: Fri Apr 03, 2020 11:36 am I am aiming to create a lookup table of SIN and COS calculations. I did glance at the ROM code for the SIN and COS commands, but backed away.
The ROM already uses tables for SIN, COS, EXP, and a few other calculations. Yeah, anything heavier than addition and subtraction is going to take a performance dive on the poor Z80—that’s a given. Creating tables always helps, especially in the 3D world. (I use a table of pre-calculated Z-axis values for the shadows in Yankee. The X and Y axes are calculated on the fly, though.)
Every man should plant a tree, build a house, and write a ZX Spectrum game.

Author of A Yankee in Iraq, a 50 fps shoot-’em-up—the first game to utilize the floating bus on the +2A/+3,
and zasm Z80 Assembler syntax highlighter.
User avatar
MonkZy
Manic Miner
Posts: 279
Joined: Thu Feb 08, 2018 1:01 pm

Re: Mucking about with 3D

Post by MonkZy »

My first machine code version of the spinning cube. This can be run in real time on real 48k hardware (uses a floating bus trick so will break on some Spectrums). I simply pre-calculated the vertices using the BASIC routine. I generated 18 frames of corner data and dumped it to a .txt file using FUSE's zx printer simulator. The edges are drawn by machine code, I used the vector routines from the incredible L Break Into Program blog. The routine manages 25fps. It takes one frame to erase all the lines and another to draw them back. I guess this can be considered a test for how long it takes to draw lines in MC. Next step is to incorporate a buffer because it is unlikely a cube over a certain size can be drawn in one frame. I want to try to calculate projected vertices in machine code next.

Image

3d-cube-asm-v1-2.tap
BASIC lookup generator

Code: Select all

10 REM 3d-cube-rotation
20 REM original code by Martin Fitzpatrick
30 REM ported by MonkZy
40 LET w=256 : LET h=128 : LET fov=100 : LET dist=4
50 LET rotx=0 : LET roty=5 : LET rotz=0 

60 BORDER 0

90 REM function and set arrays
100 DEF FN r(d) = d * PI /180
110 DIM p(8,3) : DIM e(12,2)
115 DIM o(8,3) 
120 FOR a=1 TO 8
130 FOR b=1 TO 3
140 READ p(a,b) 
150 NEXT b
160 NEXT a
170 FOR a=1 TO 12
180 READ e(a,1),e(a,2)
190 NEXT a

200 LET angx=0 : LET angy=0 : LET angz=0
210 LET bytes=0: LET f=1
230 LPRINT ";;;EDGE DATA"


290 REM calculate points
300 FOR v=1 TO 8
310 LET x=p(v,1)
320 LET y=p(v,2)
330 LET z=p(v,3)
350 GO SUB 1000
360 LET o(v,1)=ox
370 LET o(v,2)=oy
380 LET o(v,3)=oz
390 NEXT v

395 CLS
396 LPRINT :LPRINT ";;;FRAME #";f;" ";angy;" degrees"

400 FOR v=1 TO 12
410 LET x=INT(o(e(v,1),1))
420 LET y=INT(o(e(v,1),2))
430 LET x2=INT(o(e(v,2),1))
440 LET y2=INT(o(e(v,2),2))
450 PLOT x,y
460 DRAW x2-x,y2-y

461 LPRINT "     defb ";x;",";y;",";x2;",";y2
462 LET bytes=bytes+3

470 NEXT v

490 LET angx=angx+rotx
500 LET angy=angy+roty
510 LET angz=angz+rotz
520 LET f=f+1
530 IF angy<=85 THEN GO TO 290
535 LPRINT
540 LPRINT ";;;Bytes = ";bytes

999 STOP

1000 REM rotateX
1010 LET rad=FN r(angx) 
1020 LET cosa = COS rad
1030 LET sina = SIN rad
1040 LET oy = y * cosa - z * sina
1050 LET oz = y * sina + z * cosa
1060 LET y=oy:LET z=oz
1100 REM rotateY
1110 LET rad=FN r(angy)
1120 LET cosa = COS rad
1130 LET sina = SIN rad
1140 LET oz = z * cosa - x * sina
1150 LET ox = z * sina + x * cosa
1160 LET z=oz:LET x=ox
1200 REM rotateZ
1210 LET rad=FN r(angz)
1220 LET cosa = COS rad
1230 LET sina = SIN rad
1240 LET ox = x * cosa - y * sina
1250 LET oy = x * sina + y * cosa
1300 REM project
1305 LET fact=fov/(dist+z)
1310 LET ox=ox*fact + w/2
1320 LET oy=-oy*fact + h/2
1324 LET ox=ox+70
1325 LET oy=oy-23
1330 RETURN

2000 REM points
2010 DATA -1,1,-1
2020 DATA 1,1,-1
2030 DATA 1,-1,-1
2040 DATA -1,-1,-1
2050 DATA -1,1,1
2060 DATA 1,1,1
2070 DATA 1,-1,1
2080 DATA -1,-1,1

2100 REM edges
2110 DATA 1,2
2120 DATA 2,3
2130 DATA 3,4
2140 DATA 4,1
2150 DATA 6,5
2160 DATA 5,8
2170 DATA 8,7
2180 DATA 7,6
2190 DATA 1,5
2200 DATA 2,6
2210 DATA 3,7
2220 DATA 4,8
ASM

Code: Select all

		org 50000
Endless_Loop:
		ld hl,Edge_Data
		ld b,18
Frame_Loop:
		push bc				; preserve B for loop
	
		ld b,12
		push hl
Edge_Loop:
		push bc				; preserve B for loop
		ld bc,(hl)			; B = ypos1 C = xpos1
		inc hl
		inc hl
		ld de,(hl)			; D = ypos2 E = xpos2
		inc hl
		inc hl
		push hl				; preserve edge pointer
		call Draw_Line
		pop hl
  		pop bc
		djnz Edge_Loop
		
		ld bc,$40ff			; Steve Wetherill floating bus frame sync from Sidewize
		ld e,%00111010			; red ink on white paper
sync:	
		ld a,r				; padding instruction
		in a,(c)
		cp e
		jp nz,sync
		
		ld b,12
		pop hl
Erase_Loop:
		push bc				; preserve B for loop
		ld bc,(hl)			; B = ypos1 C = xpos1
		inc hl
		inc hl
		ld de,(hl)			; D = ypos2 E = xpos2
		inc hl
		inc hl
		push hl				; preserve edge pointer
		call Erase_Line
		pop hl
  		pop bc
		djnz Erase_Loop

		
		pop bc
		djnz Frame_Loop
		jp Endless_Loop
		ret	




; Plot routine
; B = Y pixel position
; C = X pixel position
;
Plot:                   CALL Get_Pixel_Address          ; Get screen address in HL, pixel position (0 to 7) in A
                        LD BC,Plot_Point                ; Address of point lookup table
                        ADD A,C                         ; Add pixel position to get entry in table
                        LD C,A
                        LD A,(BC)                       ; Get pixel data from table
                        OR (HL)                         ; OR with screen data
                        LD (HL),A                       ; Write back to screen
                        RET
 
 
; Unplot routine
; B = Y pixel position
; C = X pixel position
;
Unplot:                 CALL Get_Pixel_Address          ; Same as Plot...
                        LD BC,Unplot_Point
                        ADD A,C
                        LD C,A
                        LD A,(BC)
                        AND (HL)                        ; AND with screen data
                        LD (HL),A
                        RET


; Draw Line routine
; B = Y pixel position 1
; C = X pixel position 1
; D = Y pixel position 2
; E = X pixel position 2
;
Draw_Line:              LD A,D                          ; Check whether we are going to be drawing up
                        CP B
                        JR NC,Draw_Line_1
 
                        PUSH BC                         ; If we are, then this neat trick swaps BC and DE
                        PUSH DE                         ; using the stack, forcing the line to be always
                        POP BC                          ; drawn downwards
                        POP DE
 
Draw_Line_1:            CALL Get_Pixel_Address          ; Get screen address in HL, pixel position (0-7) in A
;
; At this point we have
;  A = Pixel position (0-7)
; HL = Screen address of the start point
; BC = Start coordinate (B=Y1, C=X1)
; DE = End coordinates  (D=Y2, E=X2)
;
                        LD IX,Plot_Point                ; Point to the Plot_Point table
                        ADD A,IXL                       ; Add the pixel position to get entry in table
                        LD IXL,A
 
                        LD A,D                          ; Calculate the line height in B (Y2-Y1)
                        SUB B
                        LD B,A
         
                        LD A,E                          ; Calculate the line width in C (X2-X1)
                        SUB C
                        JR C,Draw_Line_X1               ; If carry set (negative result) then we are drawing from right to left
;
; This bit of code mods the main loop for drawing left to right
;
                        LD C,A                          ; Store the line width
                        LD A,0x2C                       ; Code for INC L
                        LD (Draw_Line_Q1_M3),A          ; Mod the code
                        LD (Draw_Line_Q2_M3),A
                        LD A,0x0A                       ; Code for RRC D (CB 0A)
                        JR Draw_Line_X2                 ; Skip the next bit
;
; This bit of code mods the main loop for drawing right to left
;
Draw_Line_X1:           NEG                             ; The width of line is negative, so make it positive again
                        LD C,A                          ; Store the line width
                        LD A,0x2D                       ; Code for DEC L
                        LD (Draw_Line_Q1_M3),A
                        LD (Draw_Line_Q2_M3),A
                        LD A,0x02                       ; Code for RLC D (CB 02)
;
; We've got the basic information at this point
;
Draw_Line_X2:           LD (Draw_Line_Q1_M2 + 1),A      ; A contains the code for RLC D or RRC D, so make the mods
                        LD (Draw_Line_Q2_M2 + 1),A
                        LD D,(IX+0)                     ; Get the pixel data from the Point_Plot table
                        LD A,B                          ; Check if B and C are 0
                        OR C
                        JR NZ,Draw_Line_Q               ; There is a line to draw, so skip to the next bit
                        LD A,(HL)                       ; Here we've got a single point line, so plot and return
                        OR D
                        LD (HL),A
                        RET
;
; At this point
; HL = Screen address of the start point
;  B = Line height
;  C = Line width
;  D = Pixel data
;
Draw_Line_Q:            LD A,B                          ; Work out which diagonal we are on
                        CP C
                        JR NC,Draw_Line_Q2
;
; This bit of code draws the line where B<C (more horizontal than vertical)
;
Draw_Line_Q1:           LD A,C
                        LD (Draw_Line_Q1_M1 + 1),A      ; Self-mod the code again to store the line width
                        LD C,B
                        LD B,A
                        LD E,C                          ; Calculate the error value
                        SRL E
Draw_Line_Q1_L:         LD A,(HL)                       ; Plot the pixel
                        OR D
                        LD (HL),A
                        LD A,E
                        SUB C
                        LD E,A
                        JR NC,Draw_Line_Q1_M2
Draw_Line_Q1_M1:        ADD A,0                         ; Add the line height (previously stored; self modifying code)
                        LD E,A
                        CALL Pixel_Address_Down
Draw_Line_Q1_M2:        RRC D                           ; Rotate the pixel right or left; more self-modifying code
                        JR NC,Draw_Line_Q1_S
Draw_Line_Q1_M3:        INC L                           ; If we get a carry then move to adjacent screen address; more self modifying code
Draw_Line_Q1_S:         DJNZ Draw_Line_Q1_L             ; Loop until the line is drawn
                        RET
;
; This bit draws the line where B>=C (more vertical than horizontal, or diagonal)
;
Draw_Line_Q2:           LD (Draw_Line_Q2_M1 + 1),A
                        LD E,C                          ; Calculate the error value
                        SRL E
Draw_Line_Q2_L:         LD A,(HL)                       ; Plot the pixel
                        OR D
                        LD (HL),A
                        LD A,E                          ; Get the error value
                        SUB C                           ; Add the line length to it (X2-X1)
                        JR NC,Draw_Line_Q2_S            ; Skip the next bit if we don't get a carry
Draw_Line_Q2_M1:        ADD A,0                         ; Add the line height (previously stored; self modifying code)
Draw_Line_Q2_M2:        RRC D                           ; Rotates the pixel right with carry
                        JR NC,Draw_Line_Q2_S
Draw_Line_Q2_M3:        INC L                           ; If we get a carry then move to adjacent screen address; more self modifying code
Draw_Line_Q2_S:         LD E,A                          ; Store the error value back in
                        CALL Pixel_Address_Down         ; And also move down
                        DJNZ Draw_Line_Q2_L
                        RET
 
; Erase Line routine
; B = Y pixel position 1
; C = X pixel position 1
; D = Y pixel position 2
; E = X pixel position 2
;
Erase_Line:             LD A,D                          ; Check whether we are going to be drawing up
                        CP B
                        JR NC,Erase_Line_1
 
                        PUSH BC                         ; If we are, then this neat trick swaps BC and DE
                        PUSH DE                         ; using the stack, forcing the line to be always
                        POP BC                          ; drawn downwards
                        POP DE
 
Erase_Line_1:           CALL Get_Pixel_Address          ; Get screen address in HL, pixel position (0-7) in A
;
; At this point we have
;  A = Pixel position (0-7)
; HL = Screen address of the start point
; BC = Start coordinate (B=Y1, C=X1)
; DE = End coordinates  (D=Y2, E=X2)
;
                        LD IX,Unplot_Point              ; Point to the Unplot_Point table
                        ADD A,IXL                       ; Add the pixel position to get entry in table
                        LD IXL,A
 
                        LD A,D                          ; Calculate the line height in B (Y2-Y1)
                        SUB B
                        LD B,A
         
                        LD A,E                          ; Calculate the line width in C (X2-X1)
                        SUB C
                        JR C,Erase_Line_X1              ; If carry set (negative result) then we are drawing from right to left
;
; This bit of code mods the main loop for drawing left to right
;
                        LD C,A                          ; Store the line width
                        LD A,0x2C                       ; Code for INC L
                        LD (Erase_Line_Q1_M3),A         ; Mod the code
                        LD (Erase_Line_Q2_M3),A
                        LD A,0x0A                       ; Code for RRC D (CB 0A)
                        JR Erase_Line_X2                ; Skip the next bit
;
; This bit of code mods the main loop for drawing right to left
;
Erase_Line_X1:          NEG                             ; The width of line is negative, so make it positive again
                        LD C,A                          ; Store the line width
                        LD A,0x2D                       ; Code for DEC L
                        LD (Erase_Line_Q1_M3),A
                        LD (Erase_Line_Q2_M3),A
                        LD A,0x02                       ; Code for RLC D (CB 02)
;
; We've got the basic information at this point
;
Erase_Line_X2:          LD (Erase_Line_Q1_M2 + 1),A     ; A contains the code for RLC D or RRC D, so make the mods
                        LD (Erase_Line_Q2_M2 + 1),A
                        LD D,(IX+0)                     ; Get the pixel data from the Unplot_Point table
                        LD A,B                          ; Check if B and C are 0
                        OR C
                        JR NZ,Erase_Line_Q              ; There is a line to draw, so skip to the next bit
                        LD A,(HL)                       ; Here we've got a single point line, so plot and return
                        AND D
                        LD (HL),A
                        RET
;
; At this point
; HL = Screen address of the start point
;  B = Line height
;  C = Line width
;  D = Pixel data
;
Erase_Line_Q:           LD A,B                          ; Work out which diagonal we are on
                        CP C
                        JR NC,Erase_Line_Q2
;
; This bit of code draws the line where B<C (more horizontal than vertical)
;
Erase_Line_Q1:          LD A,C
                        LD (Erase_Line_Q1_M1 + 1),A     ; Self-mod the code again to store the line width
                        LD C,B
                        LD B,A
                        LD E,C                          ; Calculate the error value
                        SRL E
Erase_Line_Q1_L:        LD A,(HL)                       ; Unplot the pixel
                        AND D
                        LD (HL),A
                        LD A,E
                        SUB C
                        LD E,A
                        JR NC,Erase_Line_Q1_M2
Erase_Line_Q1_M1:       ADD A,0                         ; Add the line height (previously stored; self modifying code)
                        LD E,A
                        CALL Pixel_Address_Down
Erase_Line_Q1_M2:       RRC D                           ; Rotate the pixel right or left; more self-modifying code
                        JR C,Erase_Line_Q1_S            ; Note the change here from the Draw_Line routine
Erase_Line_Q1_M3:       INC L                           ; If we get no carry then move to adjacent screen address; more self modifying code
Erase_Line_Q1_S:        DJNZ Erase_Line_Q1_L            ; Loop until the line is drawn
                        RET
;
; This bit draws the line where B>=C (more vertical than horizontal, or diagonal)
;
Erase_Line_Q2:          LD (Erase_Line_Q2_M1 + 1),A
                        LD E,C                          ; Calculate the error value
                        SRL E
Erase_Line_Q2_L:        LD A,(HL)                       ; Unplot the pixel
                        AND D
                        LD (HL),A
                        LD A,E                          ; Get the error value
                        SUB C                           ; Add the line length to it (X2-X1)
                        JR NC,Erase_Line_Q2_S           ; Skip the next bit if we don't get a carry
Erase_Line_Q2_M1:       ADD A,0                         ; Add the line height (previously stored; self modifying code)
Erase_Line_Q2_M2:       RRC D                           ; Rotates the pixel right with carry
                        JR C,Erase_Line_Q2_S            ; Note the change here from the Draw_Line routine
Erase_Line_Q2_M3:       INC L                           ; If we get no carry then move to adjacent screen address; more self modifying code
Erase_Line_Q2_S:        LD E,A                          ; Store the error value back in
                        CALL Pixel_Address_Down         ; And also move down
                        DJNZ Erase_Line_Q2_L
                        RET

;; GET BUFFER PIXEL ADDRESS
;; B=y-pos C=x-pos 
;; Returns: HL=Adress of pixel A=Byte of the pixel

Get_Buffer_Address:

	ld l,0        ;
	ld h,b        ; B contains the Y-POS
	srl h         ;
	rr l          ;
	srl h         ;
	rr l          ; Shifts right 3x, then OR's low byte with 11100000 
	srl h         ;
	rr l          ; divide by 8?
	ld a,h        ;
	or 224        ; 11100000
	ld h,a        ;

 	ld a,c        ; C contains the X-POS
 	rra           ;
 	rra           ; divide by 8
 	rra           ;
 	and 31        ; 00011111 - strip out rolled in carry bytes
 	or l          ;
 	ld l,a        ;
 	ld a,c        ;
 	and 7         ; 00000111
 	ret           ;


; Get screen address
; B = Y pixel position
; C = X pixel position
; Returns address in HL and pixel position within character in A
;
Get_Pixel_Address:      LD A,B                          ; Calculate Y2,Y1,Y0
                        AND %00000111                   ; Mask out unwanted bits
                        OR %01000000                    ; Set base address of screen
                        LD H,A                          ; Store in H
                        LD A,B                          ; Calculate Y7,Y6
                        RRA                             ; Shift to position
                        RRA
                        RRA
                        AND %00011000                   ; Mask out unwanted bits
                        OR H                            ; OR with Y2,Y1,Y0
                        LD H,A                          ; Store in H
                        LD A,B                          ; Calculate Y5,Y4,Y3
                        RLA                             ; Shift to position
                        RLA
                        AND %11100000                   ; Mask out unwanted bits
                        LD L,A                          ; Store in L
                        LD A,C                          ; Calculate X4,X3,X2,X1,X0
                        RRA                             ; Shift into position
                        RRA
                        RRA
                        AND %00011111                   ; Mask out unwanted bits
                        OR L                            ; OR with Y5,Y4,Y3
                        LD L,A                          ; Store in L
                        LD A,C
                        AND 7
                        RET

; Move HL down one pixel line
;
Pixel_Address_Down:     INC H                           ; Go down onto the next pixel line
                        LD A,H                          ; Check if we have gone onto next character boundary
                        AND 7
                        RET NZ                          ; No, so skip the next bit
                        LD A,L                          ; Go onto the next character line
                        ADD A,32
                        LD L,A
                        RET C                           ; Check if we have gone onto next third of screen
                        LD A,H                          ; Yes, so go onto next third
                        SUB 8
                        LD H,A
                        RET
 
; Note that the functions above only work if each of these tables are in a byte boundary
;
Plot_Point:             DB %10000000,%01000000,%00100000,%00010000,%00001000,%00000100,%00000010,%00000001
Unplot_Point:           DB %01111111,%10111111,%11011111,%11101111,%11110111,%11111011,%11111101,%11111110
 
Plot_Line_LHS:          DB %11111111,%01111111,%00111111,%00011111,%00001111,%00000111,%00000011,%00000001
Plot_Line_RHS:          DB %10000000,%11000000,%11100000,%11110000,%11111000,%11111100,%11111110,%11111111

Edge_Data:

;;;EDGE DATA


;;;FRAME #1 0 degrees
     defb 164,7,231,7
     defb 231,7,231,74
     defb 231,74,164,74
     defb 164,74,164,7
     defb 218,21,178,21
     defb 178,21,178,61
     defb 178,61,218,61
     defb 218,61,218,21
     defb 164,7,178,21
     defb 231,7,218,21
     defb 231,74,218,61
     defb 164,74,178,61

;;;FRAME #2 5 degrees
     defb 162,8,229,6
     defb 229,6,229,75
     defb 229,75,162,73
     defb 162,73,162,8
     defb 220,20,180,21
     defb 180,21,180,60
     defb 180,60,220,61
     defb 220,61,220,20
     defb 162,8,180,21
     defb 229,6,220,20
     defb 229,75,220,61
     defb 162,73,180,60

;;;FRAME #3 10 degrees
     defb 161,9,226,5
     defb 226,5,226,76
     defb 226,76,161,72
     defb 161,72,161,9
     defb 222,20,182,21
     defb 182,21,182,60
     defb 182,60,222,61
     defb 222,61,222,20
     defb 161,9,182,21
     defb 226,5,222,20
     defb 226,76,222,61
     defb 161,72,182,60

;;;FRAME #4 15 degrees
     defb 160,10,223,4
     defb 223,4,223,77
     defb 223,77,160,71
     defb 160,71,160,10
     defb 224,19,184,21
     defb 184,21,184,60
     defb 184,60,224,62
     defb 224,62,224,19
     defb 160,10,184,21
     defb 223,4,224,19
     defb 223,77,224,62
     defb 160,71,184,60

;;;FRAME #5 20 degrees
     defb 160,11,219,4
     defb 219,4,219,77
     defb 219,77,160,70
     defb 160,70,160,11
     defb 225,19,186,22
     defb 186,22,186,59
     defb 186,59,225,62
     defb 225,62,225,19
     defb 160,11,186,22
     defb 219,4,225,19
     defb 219,77,225,62
     defb 160,70,186,59

;;;FRAME #6 25 degrees
     defb 160,12,216,3
     defb 216,3,216,78
     defb 216,78,160,69
     defb 160,69,160,12
     defb 227,18,188,22
     defb 188,22,188,59
     defb 188,59,227,63
     defb 227,63,227,18
     defb 160,12,188,22
     defb 216,3,227,18
     defb 216,78,227,63
     defb 160,69,188,59

;;;FRAME #7 30 degrees
     defb 160,13,211,3
     defb 211,3,211,78
     defb 211,78,160,68
     defb 160,68,160,13
     defb 229,18,191,22
     defb 191,22,191,59
     defb 191,59,229,63
     defb 229,63,229,18
     defb 160,13,191,22
     defb 211,3,229,18
     defb 211,78,229,63
     defb 160,68,191,59

;;;FRAME #8 35 degrees
     defb 160,14,207,2
     defb 207,2,207,79
     defb 207,79,160,67
     defb 160,67,160,14
     defb 230,17,193,22
     defb 193,22,193,59
     defb 193,59,230,64
     defb 230,64,230,17
     defb 160,14,193,22
     defb 207,2,230,17
     defb 207,79,230,64
     defb 160,67,193,59

;;;FRAME #9 40 degrees
     defb 161,15,202,2
     defb 202,2,202,79
     defb 202,79,161,66
     defb 161,66,161,15
     defb 232,16,195,22
     defb 195,22,195,59
     defb 195,59,232,65
     defb 232,65,232,16
     defb 161,15,195,22
     defb 202,2,232,16
     defb 202,79,232,65
     defb 161,66,195,59

;;;FRAME #10 45 degrees
     defb 162,16,198,2
     defb 198,2,198,79
     defb 198,79,162,66
     defb 162,66,162,16
     defb 233,16,198,22
     defb 198,22,198,59
     defb 198,59,233,66
     defb 233,66,233,16
     defb 162,16,198,22
     defb 198,2,233,16
     defb 198,79,233,66
     defb 162,66,198,59

;;;FRAME #11 50 degrees
     defb 163,16,193,2
     defb 193,2,193,79
     defb 193,79,163,65
     defb 163,65,163,16
     defb 234,15,200,22
     defb 200,22,200,59
     defb 200,59,234,66
     defb 234,66,234,15
     defb 163,16,200,22
     defb 193,2,234,15
     defb 193,79,234,66
     defb 163,65,200,59

;;;FRAME #12 55 degrees
     defb 165,17,188,2
     defb 188,2,188,79
     defb 188,79,165,64
     defb 165,64,165,17
     defb 235,14,202,22
     defb 202,22,202,59
     defb 202,59,235,67
     defb 235,67,235,14
     defb 165,17,202,22
     defb 188,2,235,14
     defb 188,79,235,67
     defb 165,64,202,59

;;;FRAME #13 60 degrees
     defb 166,18,184,3
     defb 184,3,184,78
     defb 184,78,166,63
     defb 166,63,166,18
     defb 235,13,204,22
     defb 204,22,204,59
     defb 204,59,235,68
     defb 235,68,235,13
     defb 166,18,204,22
     defb 184,3,235,13
     defb 184,78,235,68
     defb 166,63,204,59

;;;FRAME #14 65 degrees
     defb 168,18,179,3
     defb 179,3,179,78
     defb 179,78,168,63
     defb 168,63,168,18
     defb 235,12,207,22
     defb 207,22,207,59
     defb 207,59,235,69
     defb 235,69,235,12
     defb 168,18,207,22
     defb 179,3,235,12
     defb 179,78,235,69
     defb 168,63,207,59

;;;FRAME #15 70 degrees
     defb 170,19,176,4
     defb 176,4,176,77
     defb 176,77,170,62
     defb 170,62,170,19
     defb 235,11,209,22
     defb 209,22,209,59
     defb 209,59,235,70
     defb 235,70,235,11
     defb 170,19,209,22
     defb 176,4,235,11
     defb 176,77,235,70
     defb 170,62,209,59

;;;FRAME #16 75 degrees
     defb 171,19,172,4
     defb 172,4,172,77
     defb 172,77,171,62
     defb 171,62,171,19
     defb 235,10,211,21
     defb 211,21,211,60
     defb 211,60,235,71
     defb 235,71,235,10
     defb 171,19,211,21
     defb 172,4,235,10
     defb 172,77,235,71
     defb 171,62,211,60

;;;FRAME #17 80 degrees
     defb 173,20,169,5
     defb 169,5,169,76
     defb 169,76,173,61
     defb 173,61,173,20
     defb 234,9,213,21
     defb 213,21,213,60
     defb 213,60,234,72
     defb 234,72,234,9
     defb 173,20,213,21
     defb 169,5,234,9
     defb 169,76,234,72
     defb 173,61,213,60

;;;FRAME #18 85 degrees
     defb 175,20,166,6
     defb 166,6,166,75
     defb 166,75,175,61
     defb 175,61,175,20
     defb 233,8,215,21
     defb 215,21,215,60
     defb 215,60,233,73
     defb 233,73,233,8
     defb 175,20,215,21
     defb 166,6,233,8
     defb 166,75,233,73
     defb 175,61,215,60

;;;Bytes = 648
User avatar
djnzx48
Manic Miner
Posts: 730
Joined: Wed Dec 06, 2017 2:13 am
Location: New Zealand

Re: Mucking about with 3D

Post by djnzx48 »

Nice work! Looks like a buffer would be a good next step to add, as the output does appear to be a little flickery. Alternatively, if you're going to have a lot happening on screen, it might be faster to clear whole portions of the display rather than undrawing each individual line.

I'm wondering where the 'ld bc,(hl)' and such instructions are coming from, are they assembler extensions? Personally I avoid them since they can result in code becoming less clear, as well as introducing inefficiencies (since you can't see what they're doing internally). But feel free to keep them if you're comfortable with using them.
User avatar
Ast A. Moore
Rick Dangerous
Posts: 2641
Joined: Mon Nov 13, 2017 3:16 pm

Re: Mucking about with 3D

Post by Ast A. Moore »

djnzx48 wrote: Mon Apr 06, 2020 2:21 pm I'm wondering where the 'ld bc,(hl)' and such instructions are coming from, are they assembler extensions?
Certainly. Probably a shortcut for LD B,(HL)/*LD C,(HL+1). Yeah, I’m not a big fan of those either.
MonkZy wrote: Mon Apr 06, 2020 1:12 pm My first machine code version of the spinning cube. This can be run in real time on real 48k hardware (uses a floating bus trick so will break on some Spectrums).
This is very, very impressive! To use the floating bus on all Spectrum models, feel free to give my guide a quick read-through.
Last edited by Ast A. Moore on Mon Apr 06, 2020 3:20 pm, edited 1 time in total.
Every man should plant a tree, build a house, and write a ZX Spectrum game.

Author of A Yankee in Iraq, a 50 fps shoot-’em-up—the first game to utilize the floating bus on the +2A/+3,
and zasm Z80 Assembler syntax highlighter.
User avatar
MonkZy
Manic Miner
Posts: 279
Joined: Thu Feb 08, 2018 1:01 pm

Re: Mucking about with 3D

Post by MonkZy »

Ah, it seems Zasm does indeed compile ld bc,(hl) into :

Code: Select all

ld c,(hl)
inc hl
ld b,(hl)
dec hl
My original code was :

Code: Select all

ld c,(hl)
inc hl
ld b,(hl)
inc hl
I thought ld bc,(hl) was an optimization! Thanks for the heads up.
Firefox

Re: Mucking about with 3D

Post by Firefox »

djnzx48 wrote: Mon Apr 06, 2020 2:21 pm Looks like a buffer would be a good next step to add
I often wonder if it would be a net performance gain to compose the 3D view in a game in a back buffer that is organised linearly, then blit the whole thing to the framebuffer in one go so you only have to deal with the crazy scanline order once per frame. Especially so, bearing in mind that most 3D games have a good portion of the screen taken up by some kind of instrument panel, so the 3D view is correspondingly smaller...
User avatar
djnzx48
Manic Miner
Posts: 730
Joined: Wed Dec 06, 2017 2:13 am
Location: New Zealand

Re: Mucking about with 3D

Post by djnzx48 »

I can't speak from experience, but I think it would still be more performant to use the standard Spectrum screen layout for a backbuffer, as long as you're just drawing row-by-row up or down the screen. INC H is always going to be faster than LD A, L: ADD A, 32: LD L, A, and with the default Spectrum layout you only need to handle special cases every 8 rows. The main advantage I can see from a linear buffer is consistency/ease of use, rather than performance.

(There is a method using Gray codes that eliminates the need to add 32 for a linear buffer, but it only really works for drawing bitmaps, not vector graphics.)
User avatar
Joefish
Rick Dangerous
Posts: 2058
Joined: Tue Nov 14, 2017 10:26 am

Re: Mucking about with 3D

Post by Joefish »

If you can afford the memory, it's really efficient to have a 256x256 back-buffer (or make it two 256x128 back-buffers).
The point is you arrange the bytes in vertical strips. Then you add 1 to move down a pixel, and add 256 (+1 to the hi-byte) to move right 8 pixels.
Though you then need an optimal routine to copy it to the main screen.

You could have a look at this thread on another site about optimising line-drawing in machine code:
https://www.worldofspectrum.org/forums/ ... g-lines/p1
User avatar
Ersh
Manic Miner
Posts: 480
Joined: Mon Nov 13, 2017 1:06 pm

Re: Mucking about with 3D

Post by Ersh »

Joefish wrote: Tue Apr 07, 2020 12:40 pm If you can afford the memory, it's really efficient to have a 256x256 back-buffer (or make it two 256x128 back-buffers).
The point is you arrange the bytes in vertical strips. Then you add 1 to move down a pixel, and add 256 (+1 to the hi-byte) to move right 8 pixels.
Though you then need an optimal routine to copy it to the main screen.
I've used that technique myself in some of my demoscene productions. A 16x16 tile screen (2 bitplanes) with vertical strips to have Y linearly accessible and X by increasing the high-byte.
Firefox

Re: Mucking about with 3D

Post by Firefox »

Wow, that's a nifty bit of lateral thinking! I hadn't considered have a rotated back buffer like that! 8-)

I have done Bresenham's algorithm in the distant past, and found it a very elegant idea.

Thanks guys! That's really interesting.
User avatar
bobs
Microbot
Posts: 107
Joined: Thu Dec 28, 2017 8:26 am
Location: UK
Contact:

Re: Mucking about with 3D

Post by bobs »

My last game https://bobs-stuff.itch.io/sokobaarn used a vertical linear back buffer (VLBB) to speed things up given the amount of overdraw. And my current dev. of Melkhior’s Mansion is also using one for the exact same reasons. It’s heavy on the memory, but you can use the extra 64 bytes per column to store other data, look-up tables, colours (whatever), so it isn’t wasted.
User avatar
Joefish
Rick Dangerous
Posts: 2058
Joined: Tue Nov 14, 2017 10:26 am

Re: Mucking about with 3D

Post by Joefish »

Good point. If you did all your drawing in the bottom 3/4 of the buffer then the top 1/4 of the buffer could be used as 32 page-aligned look-up tables, each up to 64 bytes long (e.g. 32 address entries). So any screen row, attribute row, sprite-indexing, function-indexing etc. tables could go there.

When I was playing around with 3D I did waste some memory but made it easier to synch with the raster. I only rendered a 256x128 view so only needed half of the buffer. But I programmed it so that on the refresh cycle, it would wait for an interrupt, then erase the half of the buffer it wasn't using. By the time it had done that, the timing was just behind the raster, so it could copy up the 256x128 chunk it had just drawn to the main screen without any tearing. Then it'd swap to rendering on the half that was just erased. Wasteful to use two buffers instead of one, but it made the synching a whole lot easier to manage.

And anyway, apart from the code, 3D objects need far less memory to define compared to lots of sprite animations.
User avatar
777
Manic Miner
Posts: 512
Joined: Fri Jun 26, 2020 11:23 am
Location: sw uk

Re: Mucking about with 3D

Post by 777 »

MonkZy wrote: Mon Apr 06, 2020 1:12 pm
3d-cube-asm-v1-2.tap
do you have a copy of this file? the link is broken
i started programming the spectrum when i was 8 :-

1 plot rnd*255,rnd*175
2 goto 1
Post Reply