how do print to the screen using an exact pixel location in code?

The place for codemasters or beginners to talk about programming any language for the Spectrum.
Post Reply
User avatar
777
Manic Miner
Posts: 523
Joined: Fri Jun 26, 2020 11:23 am
Location: sw uk

how do print to the screen using an exact pixel location in code?

Post by 777 »

like being able to print a character at 200,100 for example? and then move it pixel by pixel if i want. im sure this is fairly easy as this is the way the spectrum displays characters anyway. and im sure ive read how to do it somewhere when i was learning assembler. any ideas? ive googled it but no joy.
i started programming the spectrum when i was 8 :-

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

http://zxspeccy.great-site.net/
User avatar
ParadigmShifter
Manic Miner
Posts: 777
Joined: Sat Sep 09, 2023 4:55 am

Re: how do print to the screen using an exact pixel location in code?

Post by ParadigmShifter »

I wrote this with some extra comments thrown in was going to maybe do a tutorial for intermediate Z80 stuff but it will do what you want (draw an 8x8 sprite anywhere on the screen*)

* Except if it's off the edges of the screen.

Code: Select all

	ORG #8000

SCRBASE	EQU	#4000
UNROLL_Sprite8x8a	EQU 1
TIMING	EQU	1
DELAYAFTERHALT	EQU	0;1

	MACRO XYTOSCRADDRHL _x_, _y_
	ld hl, SCRBASE + (((_y_&#7)|((_y_&#C0)>>3))<<8)|((_x_&#1F)|((_y_&#38)<<2))
	ENDM

	MACRO DWXYTOSCRADDR _x_, _y_
	dw SCRBASE + (((_y_&#7)|((_y_&#C0)>>3))<<8)|((_x_&#1F)|((_y_&#38)<<2))
	ENDM

	MACRO SETBORDER bdr
	ld a, bdr
	out (#FE), a
	ENDM

	MACRO PUTSPRITE8x8 _gfx_
	ld e, c
	ld a, c
	and ~7
	rra
	rra
	rra
	ld c, a
	ld a, e
	and 7
	add draw8x8/256 ; 7
	exx
	ld h, a
	ld l, 0
	ld de, _gfx_
	call jphl
	ENDM

	MACRO ERASESPRITE8x8
	ld e, c
	ld a, c
	and ~7
	rra
	rra
	rra
	ld c, a
	ld a, e
	and 7
	ld hl, erase8x8
	jr z, .docall
	inc h ; point to erase8x8shift
	ld de, erase_8x8_shifts
	rlca ; A=A*2
	add e
	ld e, a
.docall
	call jphl
	ENDM

	; DE - graphics data
	MACRO GFXCOPYSCROLL npixels
	ld bc, gfx_scrollbuff
	REPT 8
	ld h, 0
	ld a, (de)
	inc e
	ld l, a
	REPT 8 - npixels ; 7 = 11T, 6 = 22T, 5 = 33T, 4 = 44T
	add hl, hl
	ENDR
	ld a, h
	ld (bc), a
	inc c
	ld a, l
	ld (bc), a
	inc c
	ENDR
	ENDM

	; DE - graphics data
	MACRO GFXCOPYSCROLL_LT4 npixels
	ld bc, gfx_scrollbuff
	REPT 8
	xor a ; A=0 and clear carry
	ld l, a
	ld a, (de)
	inc e
	REPT npixels ; 1 = 12T, 2 = 24T, 3 = 36T
	rra ; 4T
	rr l ; 8T
	ENDR
	ld (bc), a
	inc c
	ld a, l
	ld (bc), a
	inc c
	ENDR
	ENDM


main:
	IF TIMING
		SETBORDER 4
	halt

		IF DELAYAFTERHALT
			SETBORDER 5

			; wait until raster reaches drawable area
			ld bc, 4 ; will repeat (4-1)*256 times
.delay
			djnz .delay
			dec c
			jr nz, .delay
		ENDIF

		SETBORDER 1
	ENDIF

	ld hl, playerprevy
	ld b, (hl)
	inc hl
	ld c, (hl)
	ERASESPRITE8x8

	REPT 1;4
	ld bc, 0
	PUTSPRITE8x8 gfx_smallsquare

	ld bc, 8
	PUTSPRITE8x8 gfx_checker

	ld bc, 256*8+0
	PUTSPRITE8x8 gfx_checker

	ld bc, 256*8+8
	PUTSPRITE8x8 gfx_smallsquare
	ENDR

	ld hl, playerypos
	ld de, playerprevy
	ldi
	ldi

	ld hl, playerypos
	ld b, (hl)
	inc hl
	ld c, (hl)
	ERASESPRITE8x8

	ld hl, playerypos
	ld b, (hl)
	inc hl
	ld c, (hl)
	PUTSPRITE8x8 gfx_dude;square


	IF TIMING
	SETBORDER 2
	ENDIF

	call read_keyboard

	ld hl, playerypos
	ld a, (hl)
	add b
	cp -1
	jr z, .dontupdatey
	cp 185
	jr z, .dontupdatey
	ld (hl), a
.dontupdatey
	inc hl
	ld a, (hl)
	add c
	cp -1
	jr z, .dontupdatex
	cp 249
	jr z, .dontupdatex
	ld (hl), a
.dontupdatex

	IF TIMING
		jp main
	ELSE
		ret
	ENDIF

; B: row (in character cells, so [0-23])
; C: column
sprite16x8ra:
	ld a, b
	add b ; A = B*2
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; so we now know the address...
; HL: screen address
sprite16x8raKnowAddr:
	ld de, gfx_scrollbuff
	REPT 7
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc l
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		dec l
	ENDR

	; last row, don't need to increment gfx data pointer or screen row
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	or (hl)

	ld (hl), a
	inc l
	ld a, (de)

	or (hl)

	ld (hl), a
	ret

; B: row (in pixels)
; C: column
sprite16x8:
	ld a, b
	and ~7 ; clear lower 3 bits
	rrca
	rrca ; A = B/4 so in range 0-46 which is offset into row table
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address (of row anyway)
	; adjust for row offset
	ld a, b
	and 7
	add h
	ld h, a
	; so we now know the address...
	and 7
	jr z, sprite16x8raKnowAddr ; 7/8 times: 7T, 1/8 time: 12T = 61/8 avg = 7.625T vs jp z: always 10T - win

	ld c, a
	ld a, 8
	sub c ; a = 8 - cell y offset
	ld b, a
	ld de, gfx_scrollbuff
.loop
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc l
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		dec l
		djnz .loop

	; we could split this into 2 routines depending on whether we straddle a screen third boundary or not
	; which we could work out before calling
	; then we could remove the jr c
	ld a, #20
	add l
	ld l, a
	jr c, .ok
	ld a, h
	sub #8
	ld h, a
.ok
	ld b, c
.loop2
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	or (hl)

	ld (hl), a
	inc l
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	or (hl)

	ld (hl), a
	dec l
	inc h ; next row of pixels down
	djnz .loop2
	ret

sprite16x8end:
	DISPLAY "Unused space after sprite16x8: ", /d, draw8x8 - $

	ALIGN 256
draw8x8:
	push de
	exx
	pop de
; B: row (in pixels, so [0-192])
; C: column (in character cells)
sprite8x8ca:
	ld a, b
	and ~7 ; clear lower 3 bits
	rrca
	rrca ; A = B/4 so in range 0-46 which is offset into row table
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; adjust for row offset
	ld a, b
	and 7
	add h
	ld h, a
	; so we now know the address...
; sprite8x8caKnowAddr: Sprite 8x8 column aligned, know address
; HL: screen address
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8caKnowAddr:
	ld a, h
	and 7
	jr z, sprite8x8aKnowAddr ; 7/8 times: 7T, 1/8 time: 12T = 61/8 avg = 7.625T vs jp z: always 10T - win
; sprite8x8caKnowAddrAndOffset: Sprite 8x8 column aligned, know address and cell y offset which is not 0
; A: cell Y offset, range [1-7]
; HL: screen address
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8caKnowAddrAndOffset:
	ld c, a
	ld a, 8
	sub c ; a = 8 - cell y offset
	ld b, a
; sprite8x8caKnowAddrAndBothOffsets: Sprite 8x8 column aligned, know address and cell y offset which is not 0, and number of rows to draw in 2nd cell down
; B: cell y offset, range [1-7]
; C: 8 - cell y offset (8 - B), range [1-7]
; HL: screen address
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8caKnowAddrAndBothOffsets:
.loop
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop

	; we could split this into 2 routines depending on whether we straddle a screen third boundary or not
	; which we could work out before calling
	; then we could remove the jr c
	ld a, #20
	add l
	ld l, a
	jr c, .ok
	ld a, h
	sub #8
	ld h, a
.ok
	IF 1
	ld a, (de)

	or (hl)

	ld (hl), a
	dec c
	ret z ; don't loop if we only want to draw 1 line. Is this actually faster than doing the djnz and not dec b? Looks to be slightly faster yes...
	ld b, c
.loop2
		inc e ; ok because gfx data is 8 byte aligned
		inc h ; next row of pixels down
		ld a, (de)

		or (hl)

		ld (hl), a
		djnz .loop2
	ELSE
.loop2
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop2
	ENDIF
	ret

draw8x8end:

jphl:
	jp (hl)

; B: row (in character cells, so [0-23])
; C: column
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8a:
	ld a, b
	add b ; A = B*2
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; so we now know the address...
; HL: screen address
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8aKnowAddr:
	IF UNROLL_Sprite8x8a
		REPT 7
			ld a, (de)
			inc e ; ok because gfx data is 8 byte aligned

			or (hl)

			ld (hl), a
			inc h ; next row of pixels down
		ENDR
	ELSE
		ld b, 7 ; draw 7 rows and increment gfx data pointer, screen row
.loop
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop
	ENDIF

	; last row, don't need to increment gfx data pointer or screen row
	ld a, (de)

	or (hl)

	ld (hl), a
	ret

sprite8x8end:
	DISPLAY "Unused space after sprite8x8: ", /d, draw8x8shift1 - $

	ALIGN 256
draw8x8shift1:
	GFXCOPYSCROLL_LT4 1
	exx
	jp sprite16x8
draw8x8shiftend:

	ALIGN 256
draw8x8shift2:
	GFXCOPYSCROLL_LT4 2
	exx
	jp sprite16x8
draw8x8shift2end:

	ALIGN 256
draw8x8shift3:
	GFXCOPYSCROLL_LT4 3
	exx
	jp sprite16x8
draw8x8shift3end:

	ALIGN 256
draw8x8shift4:
	GFXCOPYSCROLL 4
	exx
	jp sprite16x8
draw8x8shift4end:

	ALIGN 256
draw8x8shift5:
	GFXCOPYSCROLL 5
	exx
	jp sprite16x8
draw8x8shift5end:

	ALIGN 256
draw8x8shift6:
	GFXCOPYSCROLL 6
	exx
	jp sprite16x8
draw8x8shift6end:

	ALIGN 256
draw8x8shift7:
	GFXCOPYSCROLL 7
	exx
	jp sprite16x8
draw8x8shift7end:

	ALIGN 256
erase8x8:
; B: row (in pixels, so [0-192])
; C: column (in character cells)
erase8x8ca:
	ld a, b
	and ~7 ; clear lower 3 bits
	rrca
	rrca ; A = B/4 so in range 0-46 which is offset into row table
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; adjust for row offset
	ld a, b
	and 7
	add h
	ld h, a
	; so we now know the address...
; erase8x8caKnowAddr: Sprite 8x8 column aligned, know address
; HL: screen address
erase8x8caKnowAddr:
	ld a, h
	and 7
	jr z, erase8x8aKnowAddr ; 7/8 times: 7T, 1/8 time: 12T = 61/8 avg = 7.625T vs jp z: always 10T - win
; erase8x8caKnowAddrAndOffset: Sprite 8x8 column aligned, know address and cell y offset which is not 0
; A: cell Y offset, range [1-7]
; HL: screen address
erase8x8caKnowAddrAndOffset:
	ld c, a
	ld a, 8
	sub c ; a = 8 - cell y offset
	ld b, a
; erase8x8caKnowAddrAndBothOffsets: Sprite 8x8 column aligned, know address and cell y offset which is not 0, and number of rows to draw in 2nd cell down
; B: cell y offset, range [1-7]
; C: 8 - cell y offset (8 - B), range [1-7]
; HL: screen address
erase8x8caKnowAddrAndBothOffsets:
	xor a

.loop
		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop

	; we could split this into 2 routines depending on whether we straddle a screen third boundary or not
	; which we could work out before calling
	; then we could remove the jr c
	ld a, #20
	add l
	ld l, a
	jr c, .ok
	ld a, h
	sub #8
	ld h, a
.ok
	xor a

	ld b, c
	IF 1
	dec b
	ld (hl), a
	ret z ; don't loop if we only want to draw 1 line. Is this actually faster than doing the djnz and not dec b? Looks to be slightly faster yes...
.loop2
		inc h ; next row of pixels down
		ld (hl), a
		djnz .loop2
	ELSE
.loop2
		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop2
	ENDIF
	ret

; B: row (in character cells, so [0-23])
; C: column
erase8x8a:
	ld a, b
	add b ; A = B*2
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; so we now know the address...
; HL: screen address
erase8x8aKnowAddr:
	xor a

	REPT 7
		ld (hl), a
		inc h ; next row of pixels down
	ENDR

	ld (hl), a
	ret
erase8x8end:

	ALIGN 256
erase8x8shift:
; B: row (in pixels)
; C: column
erase16x8:
	ld a, b
	and ~7 ; clear lower 3 bits
	rrca
	rrca ; A = B/4 so in range 0-46 which is offset into row table
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address (of row anyway)
	; adjust for row offset
	ld a, b
	and 7
	add h
	ld h, a
	; so we now know the address...
	and 7
	jr z, erase16x8raKnowAddr ; 7/8 times: 7T, 1/8 time: 12T = 61/8 avg = 7.625T vs jp z: always 10T - win

	ld c, a
	ld a, 8
	sub c ; a = 8 - cell y offset
	ld b, a

.loop
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		and (hl)

		ld (hl), a
		inc l
		ld a, (de)
		dec e

		and (hl)

		ld (hl), a
		inc h ; next row of pixels down
		dec l
		djnz .loop

	; we could split this into 2 routines depending on whether we straddle a screen third boundary or not
	; which we could work out before calling
	; then we could remove the jr c
	ld a, #20
	add l
	ld l, a
	jr c, .ok
	ld a, h
	sub #8
	ld h, a
.ok
	ld b, c
.loop2
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	and (hl)

	ld (hl), a
	inc l
	ld a, (de)
	dec e

	and (hl)

	ld (hl), a
	dec l
	inc h ; next row of pixels down
	djnz .loop2
	ret

; B: row (in character cells, so [0-23])
; C: column
erase16x8ra:
	ld a, b
	add b ; A = B*2
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; so we now know the address...
; HL: screen address
erase16x8raKnowAddr:

	REPT 7
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		and (hl)

		ld (hl), a
		inc l
		ld a, (de)
		dec e

		and (hl)

		ld (hl), a
		inc h ; next row of pixels down
		dec l
	ENDR

	; last row, don't need to increment gfx data pointer or screen row
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	and (hl)

	ld (hl), a
	inc l
	ld a, (de)

	and (hl)

	ld (hl), a
	ret

; at exit, B contains 1 if we pressed down and -1 if we pressed up
; at exit, C contains 1 if we pressed right and -1 if we pressed left
read_keyboard:
	; Read these ports to scan keyboard
	; bit N (0-based) is clear if the key is being pressed
	; #FE - SHIFT, Z, X, C, & V
	; #FD - A, S, D, F, & G
	; #FB - Q, W, E, R, & T
	; #F7 - 1, 2, 3, 4, & 5
	; #EF - 0, 9, 8, 7, & 6
	; #DF - P, O, I, U, & Y
	; #BF - ENTER, L, K, J, & H
	; #7F - SPACE, FULL-STOP, M, N, & B
	; ld a, port
	; in a, (#FE)
	; to do the read of the port

	ld bc, 0

	; are we pressing W?
	ld a, #FB
	in a, (#FE)
	bit 1, a
	jr nz, .notpressingW
	dec b
.notpressingW
	; are we pressing A, S or D?
	ld a, #FD
	in a, (#FE)
	bit 1, a
	jr nz, .notpressingS
	inc b
.notpressingS
	; are we pressing A?
	bit 0, a
	jr nz, .notpressingA
	dec c
.notpressingA
	; are we pressing D?
	bit 2, a
	jr nz, .notpressingD
	inc c
.notpressingD
	ret

	ALIGN 256
tbl_rows
	REPT 24, row
	DWXYTOSCRADDR 0, row*8
	ENDR

	ALIGN 16
gfx_scrollbuff BLOCK 16 ; buffer for scrolling 8x8 sprites per pixel right/left

	ALIGN 8
gfx_square	dg ########
			dg #......#
			dg #......#
			dg #......#
			dg #......#
			dg #......#
			dg #......#
			dg ########		

gfx_smallsquare	dg ........
				dg .######.
				dg .######.
				dg .######.
				dg .######.
				dg .######.
				dg .######.
				dg ........		
			
gfx_dude	dg ..####..
			dg .##.#.#.
			dg .######.
			dg ..####..
			dg ...##...
			dg .######.
			dg ..####..
			dg ..##.##.

gfx_checker	db #55, #AA, #55, #AA, #55, #AA, #55, #AA

gfx_blank BLOCK 8
gfx_solid BLOCK 8, #FF

	ALIGN 16
erase_8x8_shifts	dw 0 ; dummy data, can be used for something else
					db %10000000, %01111111
					db %11000000, %00111111
					db %11100000, %00011111
					db %11110000, %00001111
					db %11111000, %00000111
					db %11111100, %00000011
					db %11111110, %00000001


playerypos db 0
playerxpos db 0
playerprevy	db 0
playerprevx	db 0
User avatar
777
Manic Miner
Posts: 523
Joined: Fri Jun 26, 2020 11:23 am
Location: sw uk

Re: how do print to the screen using an exact pixel location in code?

Post by 777 »

ParadigmShifter wrote: Mon Apr 29, 2024 3:00 am I wrote this with some extra comments thrown in was going to maybe do a tutorial for intermediate Z80 stuff but it will do what you want (draw an 8x8 sprite anywhere on the screen*)

* Except if it's off the edges of the screen.

Code: Select all

	ORG #8000

SCRBASE	EQU	#4000
UNROLL_Sprite8x8a	EQU 1
TIMING	EQU	1
DELAYAFTERHALT	EQU	0;1

	MACRO XYTOSCRADDRHL _x_, _y_
	ld hl, SCRBASE + (((_y_&#7)|((_y_&#C0)>>3))<<8)|((_x_&#1F)|((_y_&#38)<<2))
	ENDM

	MACRO DWXYTOSCRADDR _x_, _y_
	dw SCRBASE + (((_y_&#7)|((_y_&#C0)>>3))<<8)|((_x_&#1F)|((_y_&#38)<<2))
	ENDM

	MACRO SETBORDER bdr
	ld a, bdr
	out (#FE), a
	ENDM

	MACRO PUTSPRITE8x8 _gfx_
	ld e, c
	ld a, c
	and ~7
	rra
	rra
	rra
	ld c, a
	ld a, e
	and 7
	add draw8x8/256 ; 7
	exx
	ld h, a
	ld l, 0
	ld de, _gfx_
	call jphl
	ENDM

	MACRO ERASESPRITE8x8
	ld e, c
	ld a, c
	and ~7
	rra
	rra
	rra
	ld c, a
	ld a, e
	and 7
	ld hl, erase8x8
	jr z, .docall
	inc h ; point to erase8x8shift
	ld de, erase_8x8_shifts
	rlca ; A=A*2
	add e
	ld e, a
.docall
	call jphl
	ENDM

	; DE - graphics data
	MACRO GFXCOPYSCROLL npixels
	ld bc, gfx_scrollbuff
	REPT 8
	ld h, 0
	ld a, (de)
	inc e
	ld l, a
	REPT 8 - npixels ; 7 = 11T, 6 = 22T, 5 = 33T, 4 = 44T
	add hl, hl
	ENDR
	ld a, h
	ld (bc), a
	inc c
	ld a, l
	ld (bc), a
	inc c
	ENDR
	ENDM

	; DE - graphics data
	MACRO GFXCOPYSCROLL_LT4 npixels
	ld bc, gfx_scrollbuff
	REPT 8
	xor a ; A=0 and clear carry
	ld l, a
	ld a, (de)
	inc e
	REPT npixels ; 1 = 12T, 2 = 24T, 3 = 36T
	rra ; 4T
	rr l ; 8T
	ENDR
	ld (bc), a
	inc c
	ld a, l
	ld (bc), a
	inc c
	ENDR
	ENDM


main:
	IF TIMING
		SETBORDER 4
	halt

		IF DELAYAFTERHALT
			SETBORDER 5

			; wait until raster reaches drawable area
			ld bc, 4 ; will repeat (4-1)*256 times
.delay
			djnz .delay
			dec c
			jr nz, .delay
		ENDIF

		SETBORDER 1
	ENDIF

	ld hl, playerprevy
	ld b, (hl)
	inc hl
	ld c, (hl)
	ERASESPRITE8x8

	REPT 1;4
	ld bc, 0
	PUTSPRITE8x8 gfx_smallsquare

	ld bc, 8
	PUTSPRITE8x8 gfx_checker

	ld bc, 256*8+0
	PUTSPRITE8x8 gfx_checker

	ld bc, 256*8+8
	PUTSPRITE8x8 gfx_smallsquare
	ENDR

	ld hl, playerypos
	ld de, playerprevy
	ldi
	ldi

	ld hl, playerypos
	ld b, (hl)
	inc hl
	ld c, (hl)
	ERASESPRITE8x8

	ld hl, playerypos
	ld b, (hl)
	inc hl
	ld c, (hl)
	PUTSPRITE8x8 gfx_dude;square


	IF TIMING
	SETBORDER 2
	ENDIF

	call read_keyboard

	ld hl, playerypos
	ld a, (hl)
	add b
	cp -1
	jr z, .dontupdatey
	cp 185
	jr z, .dontupdatey
	ld (hl), a
.dontupdatey
	inc hl
	ld a, (hl)
	add c
	cp -1
	jr z, .dontupdatex
	cp 249
	jr z, .dontupdatex
	ld (hl), a
.dontupdatex

	IF TIMING
		jp main
	ELSE
		ret
	ENDIF

; B: row (in character cells, so [0-23])
; C: column
sprite16x8ra:
	ld a, b
	add b ; A = B*2
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; so we now know the address...
; HL: screen address
sprite16x8raKnowAddr:
	ld de, gfx_scrollbuff
	REPT 7
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc l
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		dec l
	ENDR

	; last row, don't need to increment gfx data pointer or screen row
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	or (hl)

	ld (hl), a
	inc l
	ld a, (de)

	or (hl)

	ld (hl), a
	ret

; B: row (in pixels)
; C: column
sprite16x8:
	ld a, b
	and ~7 ; clear lower 3 bits
	rrca
	rrca ; A = B/4 so in range 0-46 which is offset into row table
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address (of row anyway)
	; adjust for row offset
	ld a, b
	and 7
	add h
	ld h, a
	; so we now know the address...
	and 7
	jr z, sprite16x8raKnowAddr ; 7/8 times: 7T, 1/8 time: 12T = 61/8 avg = 7.625T vs jp z: always 10T - win

	ld c, a
	ld a, 8
	sub c ; a = 8 - cell y offset
	ld b, a
	ld de, gfx_scrollbuff
.loop
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc l
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		dec l
		djnz .loop

	; we could split this into 2 routines depending on whether we straddle a screen third boundary or not
	; which we could work out before calling
	; then we could remove the jr c
	ld a, #20
	add l
	ld l, a
	jr c, .ok
	ld a, h
	sub #8
	ld h, a
.ok
	ld b, c
.loop2
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	or (hl)

	ld (hl), a
	inc l
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	or (hl)

	ld (hl), a
	dec l
	inc h ; next row of pixels down
	djnz .loop2
	ret

sprite16x8end:
	DISPLAY "Unused space after sprite16x8: ", /d, draw8x8 - $

	ALIGN 256
draw8x8:
	push de
	exx
	pop de
; B: row (in pixels, so [0-192])
; C: column (in character cells)
sprite8x8ca:
	ld a, b
	and ~7 ; clear lower 3 bits
	rrca
	rrca ; A = B/4 so in range 0-46 which is offset into row table
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; adjust for row offset
	ld a, b
	and 7
	add h
	ld h, a
	; so we now know the address...
; sprite8x8caKnowAddr: Sprite 8x8 column aligned, know address
; HL: screen address
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8caKnowAddr:
	ld a, h
	and 7
	jr z, sprite8x8aKnowAddr ; 7/8 times: 7T, 1/8 time: 12T = 61/8 avg = 7.625T vs jp z: always 10T - win
; sprite8x8caKnowAddrAndOffset: Sprite 8x8 column aligned, know address and cell y offset which is not 0
; A: cell Y offset, range [1-7]
; HL: screen address
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8caKnowAddrAndOffset:
	ld c, a
	ld a, 8
	sub c ; a = 8 - cell y offset
	ld b, a
; sprite8x8caKnowAddrAndBothOffsets: Sprite 8x8 column aligned, know address and cell y offset which is not 0, and number of rows to draw in 2nd cell down
; B: cell y offset, range [1-7]
; C: 8 - cell y offset (8 - B), range [1-7]
; HL: screen address
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8caKnowAddrAndBothOffsets:
.loop
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop

	; we could split this into 2 routines depending on whether we straddle a screen third boundary or not
	; which we could work out before calling
	; then we could remove the jr c
	ld a, #20
	add l
	ld l, a
	jr c, .ok
	ld a, h
	sub #8
	ld h, a
.ok
	IF 1
	ld a, (de)

	or (hl)

	ld (hl), a
	dec c
	ret z ; don't loop if we only want to draw 1 line. Is this actually faster than doing the djnz and not dec b? Looks to be slightly faster yes...
	ld b, c
.loop2
		inc e ; ok because gfx data is 8 byte aligned
		inc h ; next row of pixels down
		ld a, (de)

		or (hl)

		ld (hl), a
		djnz .loop2
	ELSE
.loop2
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop2
	ENDIF
	ret

draw8x8end:

jphl:
	jp (hl)

; B: row (in character cells, so [0-23])
; C: column
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8a:
	ld a, b
	add b ; A = B*2
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; so we now know the address...
; HL: screen address
; DE: 8 rows 8x1 sprite data (8 byte aligned)
sprite8x8aKnowAddr:
	IF UNROLL_Sprite8x8a
		REPT 7
			ld a, (de)
			inc e ; ok because gfx data is 8 byte aligned

			or (hl)

			ld (hl), a
			inc h ; next row of pixels down
		ENDR
	ELSE
		ld b, 7 ; draw 7 rows and increment gfx data pointer, screen row
.loop
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		or (hl)

		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop
	ENDIF

	; last row, don't need to increment gfx data pointer or screen row
	ld a, (de)

	or (hl)

	ld (hl), a
	ret

sprite8x8end:
	DISPLAY "Unused space after sprite8x8: ", /d, draw8x8shift1 - $

	ALIGN 256
draw8x8shift1:
	GFXCOPYSCROLL_LT4 1
	exx
	jp sprite16x8
draw8x8shiftend:

	ALIGN 256
draw8x8shift2:
	GFXCOPYSCROLL_LT4 2
	exx
	jp sprite16x8
draw8x8shift2end:

	ALIGN 256
draw8x8shift3:
	GFXCOPYSCROLL_LT4 3
	exx
	jp sprite16x8
draw8x8shift3end:

	ALIGN 256
draw8x8shift4:
	GFXCOPYSCROLL 4
	exx
	jp sprite16x8
draw8x8shift4end:

	ALIGN 256
draw8x8shift5:
	GFXCOPYSCROLL 5
	exx
	jp sprite16x8
draw8x8shift5end:

	ALIGN 256
draw8x8shift6:
	GFXCOPYSCROLL 6
	exx
	jp sprite16x8
draw8x8shift6end:

	ALIGN 256
draw8x8shift7:
	GFXCOPYSCROLL 7
	exx
	jp sprite16x8
draw8x8shift7end:

	ALIGN 256
erase8x8:
; B: row (in pixels, so [0-192])
; C: column (in character cells)
erase8x8ca:
	ld a, b
	and ~7 ; clear lower 3 bits
	rrca
	rrca ; A = B/4 so in range 0-46 which is offset into row table
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; adjust for row offset
	ld a, b
	and 7
	add h
	ld h, a
	; so we now know the address...
; erase8x8caKnowAddr: Sprite 8x8 column aligned, know address
; HL: screen address
erase8x8caKnowAddr:
	ld a, h
	and 7
	jr z, erase8x8aKnowAddr ; 7/8 times: 7T, 1/8 time: 12T = 61/8 avg = 7.625T vs jp z: always 10T - win
; erase8x8caKnowAddrAndOffset: Sprite 8x8 column aligned, know address and cell y offset which is not 0
; A: cell Y offset, range [1-7]
; HL: screen address
erase8x8caKnowAddrAndOffset:
	ld c, a
	ld a, 8
	sub c ; a = 8 - cell y offset
	ld b, a
; erase8x8caKnowAddrAndBothOffsets: Sprite 8x8 column aligned, know address and cell y offset which is not 0, and number of rows to draw in 2nd cell down
; B: cell y offset, range [1-7]
; C: 8 - cell y offset (8 - B), range [1-7]
; HL: screen address
erase8x8caKnowAddrAndBothOffsets:
	xor a

.loop
		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop

	; we could split this into 2 routines depending on whether we straddle a screen third boundary or not
	; which we could work out before calling
	; then we could remove the jr c
	ld a, #20
	add l
	ld l, a
	jr c, .ok
	ld a, h
	sub #8
	ld h, a
.ok
	xor a

	ld b, c
	IF 1
	dec b
	ld (hl), a
	ret z ; don't loop if we only want to draw 1 line. Is this actually faster than doing the djnz and not dec b? Looks to be slightly faster yes...
.loop2
		inc h ; next row of pixels down
		ld (hl), a
		djnz .loop2
	ELSE
.loop2
		ld (hl), a
		inc h ; next row of pixels down
		djnz .loop2
	ENDIF
	ret

; B: row (in character cells, so [0-23])
; C: column
erase8x8a:
	ld a, b
	add b ; A = B*2
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; so we now know the address...
; HL: screen address
erase8x8aKnowAddr:
	xor a

	REPT 7
		ld (hl), a
		inc h ; next row of pixels down
	ENDR

	ld (hl), a
	ret
erase8x8end:

	ALIGN 256
erase8x8shift:
; B: row (in pixels)
; C: column
erase16x8:
	ld a, b
	and ~7 ; clear lower 3 bits
	rrca
	rrca ; A = B/4 so in range 0-46 which is offset into row table
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address (of row anyway)
	; adjust for row offset
	ld a, b
	and 7
	add h
	ld h, a
	; so we now know the address...
	and 7
	jr z, erase16x8raKnowAddr ; 7/8 times: 7T, 1/8 time: 12T = 61/8 avg = 7.625T vs jp z: always 10T - win

	ld c, a
	ld a, 8
	sub c ; a = 8 - cell y offset
	ld b, a

.loop
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		and (hl)

		ld (hl), a
		inc l
		ld a, (de)
		dec e

		and (hl)

		ld (hl), a
		inc h ; next row of pixels down
		dec l
		djnz .loop

	; we could split this into 2 routines depending on whether we straddle a screen third boundary or not
	; which we could work out before calling
	; then we could remove the jr c
	ld a, #20
	add l
	ld l, a
	jr c, .ok
	ld a, h
	sub #8
	ld h, a
.ok
	ld b, c
.loop2
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	and (hl)

	ld (hl), a
	inc l
	ld a, (de)
	dec e

	and (hl)

	ld (hl), a
	dec l
	inc h ; next row of pixels down
	djnz .loop2
	ret

; B: row (in character cells, so [0-23])
; C: column
erase16x8ra:
	ld a, b
	add b ; A = B*2
	ld h, tbl_rows/256 ; high byte of screen address lookup table. Aligned 256 so low byte will be just row*2
	ld l, a ; index into table 
	ld a, (hl) ; low byte of screen address
	inc l ; point HL to high byte of screen address
	ld h, (hl) ; read high byte of screen address
	add c ; add on column to low byte of screen address
	ld l, a ; and write it back. HL now holds correct screen address
	; so we now know the address...
; HL: screen address
erase16x8raKnowAddr:

	REPT 7
		ld a, (de)
		inc e ; ok because gfx data is 8 byte aligned

		and (hl)

		ld (hl), a
		inc l
		ld a, (de)
		dec e

		and (hl)

		ld (hl), a
		inc h ; next row of pixels down
		dec l
	ENDR

	; last row, don't need to increment gfx data pointer or screen row
	ld a, (de)
	inc e ; ok because gfx data is 8 byte aligned

	and (hl)

	ld (hl), a
	inc l
	ld a, (de)

	and (hl)

	ld (hl), a
	ret

; at exit, B contains 1 if we pressed down and -1 if we pressed up
; at exit, C contains 1 if we pressed right and -1 if we pressed left
read_keyboard:
	; Read these ports to scan keyboard
	; bit N (0-based) is clear if the key is being pressed
	; #FE - SHIFT, Z, X, C, & V
	; #FD - A, S, D, F, & G
	; #FB - Q, W, E, R, & T
	; #F7 - 1, 2, 3, 4, & 5
	; #EF - 0, 9, 8, 7, & 6
	; #DF - P, O, I, U, & Y
	; #BF - ENTER, L, K, J, & H
	; #7F - SPACE, FULL-STOP, M, N, & B
	; ld a, port
	; in a, (#FE)
	; to do the read of the port

	ld bc, 0

	; are we pressing W?
	ld a, #FB
	in a, (#FE)
	bit 1, a
	jr nz, .notpressingW
	dec b
.notpressingW
	; are we pressing A, S or D?
	ld a, #FD
	in a, (#FE)
	bit 1, a
	jr nz, .notpressingS
	inc b
.notpressingS
	; are we pressing A?
	bit 0, a
	jr nz, .notpressingA
	dec c
.notpressingA
	; are we pressing D?
	bit 2, a
	jr nz, .notpressingD
	inc c
.notpressingD
	ret

	ALIGN 256
tbl_rows
	REPT 24, row
	DWXYTOSCRADDR 0, row*8
	ENDR

	ALIGN 16
gfx_scrollbuff BLOCK 16 ; buffer for scrolling 8x8 sprites per pixel right/left

	ALIGN 8
gfx_square	dg ########
			dg #......#
			dg #......#
			dg #......#
			dg #......#
			dg #......#
			dg #......#
			dg ########		

gfx_smallsquare	dg ........
				dg .######.
				dg .######.
				dg .######.
				dg .######.
				dg .######.
				dg .######.
				dg ........		
			
gfx_dude	dg ..####..
			dg .##.#.#.
			dg .######.
			dg ..####..
			dg ...##...
			dg .######.
			dg ..####..
			dg ..##.##.

gfx_checker	db #55, #AA, #55, #AA, #55, #AA, #55, #AA

gfx_blank BLOCK 8
gfx_solid BLOCK 8, #FF

	ALIGN 16
erase_8x8_shifts	dw 0 ; dummy data, can be used for something else
					db %10000000, %01111111
					db %11000000, %00111111
					db %11100000, %00011111
					db %11110000, %00001111
					db %11111000, %00000111
					db %11111100, %00000011
					db %11111110, %00000001


playerypos db 0
playerxpos db 0
playerprevy	db 0
playerprevx	db 0
thank you. what assembler did you use? it doesnt seem to like the zx spin one
i started programming the spectrum when i was 8 :-

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

http://zxspeccy.great-site.net/
User avatar
ParadigmShifter
Manic Miner
Posts: 777
Joined: Sat Sep 09, 2023 4:55 am

Re: how do print to the screen using an exact pixel location in code?

Post by ParadigmShifter »

I use sjasmplus. To compile

sjasmplus.exe --sym=out.sym --syntax=f --raw=out.bin src.asm

Where src.asm is name of the file
User avatar
R-Tape
Site Admin
Posts: 6467
Joined: Thu Nov 09, 2017 11:46 am

Re: how do print to the screen using an exact pixel location in code?

Post by R-Tape »

777 wrote: Mon Apr 29, 2024 2:14 am im sure this is fairly easy as this is the way the spectrum displays characters anyway.
I'm afraid not! The spectrum's display is designed with easy printing of characters at set positions of columns and rows—not pixel positions.

My beginner's sprite routine might help. Have a read of the thread as it gets updated throughout, the first piece of code is in the second post. It assembles in ZX-Spin. Once you can draw and move a sprite, you can modify it for a smaller character.
AndyC
Dynamite Dan
Posts: 1428
Joined: Mon Nov 13, 2017 5:12 am

Re: how do print to the screen using an exact pixel location in code?

Post by AndyC »

777 wrote: Mon Apr 29, 2024 2:14 am im sure this is fairly easy as this is the way the spectrum displays characters anyway.
It's actually not the most simple thing and notably something Sinclair BASIC can't do as a result. The ROM routines will only print characters 8 pixel aligned (which is easier because you only have to work a byte at a time) and only every 8 rows (which is easier because you never have to cross a screen boundary).

The best way to do this, is to work it out yourself. Sure you can just copy someone's routine, but this is one of the best bits of code for learning asm commands and understanding the hardware.

Personally I'd break it down like this:

1) write a routine that can "print" a character at any given character position, without using ROM routines. Just a matter of finding the right location, and then copying 8 bytes (calculating next row address as you go).

2) tweak that routine to allow the Y position to be any line. You'll have to adapt the "next line" code to cope with crossing between thirds of the screen. You'll also want to think about clipping a character if it'll go off the bottom of the screen. Bonus points for thinking about how to print characters just off the top of the screen with just the bottom parts visible.

3) tweak that routine to allow the X position to be in any pixel. Now you'll have to think about how the character pattern needs to be shifted since it will straddle multiple byte boundaries. You'll also need to think about how you'll deal with the background (just draw the on pixels? XOR it? Erase the 8 pixels first to ensure the character looks right?) Clipping at the edges again becomes another challenge.

Do all that and you'll be a much more confident assembly programmer and well on the way to dealing with the kind of issues you'll face when drawing sprites etc.
Post Reply