Jump to content
IGNORED

WIP Vulcano 1k Minigame - Feedback needed


Heaven/TQA

Recommended Posts

hi guys,

 

attachted a wip build of vulcano 1k (whirlwind 2006). i just played around with sound. can you please give me your feedback if the sound is too disturbing or is it fitting to the game? it should put the player into stress... ;)

 

the score routines is in place (see the changes in the score) but not the mechanics as the scoring is not ironed out yet.

 

further you can move the shitty car from left to right but this gfx is just a simple place holder and will be multicolour same as the small man which will be animated somehow as well...

 

havent tried the game on real machine yet just atari800win... the interesting thing is that in PAL more stones are falling down than in NTSC mode...

vulcano.zip

Link to comment
Share on other sites

The sound is too annoying.

 

Why are the rainbow colours moving? That effect is a bit annoying too.

 

The ambulance doesn't move with diagonals.

 

A cheap way to cope with that is to just use the PTRIG (0,1) shadows for l/r movement - the OS routine saves you needing tables, masks or bitshifts which might save you some valuable bytes.

Link to comment
Share on other sites

thanks for feedback.

 

the rainbow colours are interlacing and producing 16 colours for the background. it will not be noticable on real machine but even in atari800win fullscreen mode you should get the interlace fx.

 

OS is completly switched off to have full processor power + zero page.

 

joystick routines. diagonals will be implemented in the next release as i am using the routine from Boinxx & Venus.

 

so... what to do with the sounds?

 

i was thinking as well about a "asteroid" or "centipede"-like background msx which gets faster while you are playing... would this be better?

Link to comment
Share on other sites

small update.

 

- joystick routine changed. should be easier now to navigate

- 1st collision implemented. drive to the man, pick him up and move back.

- timebar included. it does nothing at the moment but moves slowly

- sound disabled

 

the sprites are still mono-colours but will be coloured via rasterinterrupts.

 

dont worry about the 1k size... i waste a lot of space. i will squeeze gfx and data/code when the game is finished...

vulcano.zip

post-528-1148233626_thumb.png

Link to comment
Share on other sites

Still not a fan of that moving rainbow effect.

 

I assume the rocks will destroy man / ambulance?

 

Possible ideas:

 

Maybe have a time penalty + damage when a rock hits ambulance?

 

Have score for rescuing man increase for consecutive rescues, but reset when 1 is missed.

 

Have the man appear in random positions. Have the drop-off point appear randomly at left or right of screen.

Link to comment
Share on other sites

rybags... the collision detection car/rock will be next.

 

time penalty/bonus score will be implemented that's for what the time bar is used for.

 

i thought when the rock hits the ambulance the game is over... or how do you think the player could miss the man? i like the idea of "combo points" but don't get it how can i miss... maybe you ment that i have picked up the man but could not rescue him?

Link to comment
Share on other sites

here is the level table... you can find it at $4800ff (after the display list9... so you can enter monitor by hitting F8 and play around with the values. restart with "cont". ;)

 

;***** level data (1-10)

 

mantab dta 2,4,6,10,14,18,26,34,42,50

scoretab dta 2,2,2,4,4,4,8,8,8,10 ;*100

;NTSC tab * 60, PAL * 50

timetabl dta <360,<480,<540,<600,<850,<1080,<1320,<1560,<1680,<1800

timetabh dta >360,>480,>540,>600,>850,>1080,>1320,>1560,>1680,>1800

nexttab dta 120,60,40,30,25,20,15,10,9,8

Link to comment
Share on other sites

the drop rate of the asteroids is "nexttab". how many VBLs to wait for releasing a new one. scoretab is the bonus you get for rescuing man, mantab how many men you have to rescue for next level...

 

timetabl,h is not working yet... it should become the values for the time out bar... so how much time you have for rescue one man...

Link to comment
Share on other sites

hmm.... i went through the source code and at the moment i can not see any big improvements to save memory.... the preshifted asteroids in the source code should be packed well by Flashpack2.1 but i am not sure... i'll test it with own preshift routines...

 

then i see improvments when using a "general init routine" which initialises the zeropage/antic/gtia via tables and not with lda,sta...

 

any more ideas?

 

;***** Vulcano 1K
;***** for Minigame Compo 2006 
;***** written by Heaven/TQA
;***** start: 06/05/07


;**** to do's
;**** 1. title screen
;**** 2. car sprite
;**** 3. man sprite - done
;**** 4. game logic
;**** 5. music/jingles
;**** 6. pal/ntsc

vram	equ $6000
sprites	equ $5000
p0		equ $5400
p1		equ $5500
p2		equ $5600
p3		equ $5700
font	equ $8000

wsync	equ $d40a
vcount	equ $d40b
dliv	equ $200
dlistv	equ $d402
soundf0	equ $d200
soundc0	equ $d201
soundctl equ $d208

hitclr	equ $d01e
colp0pl	equ $d00c
colp0pf	equ $d004

;***** zeropage
vbl_flag	equ 0	;will be decremented each VBL
var1	equ 1
interlace equ 3		;flag to delay DLI every 2nd VBL
var2	equ 4
flash_counter equ 6	;counter for switching on the lights
scr_pointer equ 7
save_a	equ 9
save_x	equ 10
save_y	equ 11

next_stone equ 12	;counter when next appears
start_kernel equ 13
level	equ 14		;level

score	equ 15		;15-17 in BCD
stick0	equ 18
car_pos_x equ 19	;car screen position
car_dir	equ 20

;***** sirene vars
siren_delay	equ 21
siren_mode	equ 22
siren_freq	equ 23

;timer
timer_pos	equ 24	;16 bit
timer_add	equ 26	;16 bit

pickup_flag equ 28
next_level	equ 29	;how many men to pick up
skyv		equ 30
end_flag	equ 32

	org $4000
start	jsr set_skyscraper

font_copy	ldx #0
font_copy_loop lda $e080,x
	sta font+48*8,x
	inx
	cpx #80
	bne font_copy_loop
	
	jsr switch_off_os_rom
	jsr wait_vbl
	jsr pm_init
	mva #$80 $d409
	mva #62 $d400
	mwa #dlist dlistv
	mva #4 $d016
	mva #8 $d017
	mva #2 $d019
start_game lda 53279
	cmp #6
	bne start_game
	mva #0 interlace
	sta score
	sta score+1
	sta score+2
	sta level
	sta end_flag			
	sta car_dir
	jsr write_score
	mva #8 var1
	sta hitclr
	mva #$30 car_pos_x
	
main	ldx level
	lda timetabl,x
	sta timer_add
	lda timetabh,x
	sta timer_add+1
	lda mantab,x
	sta next_level

;loop99	jmp loop99
	mva #0 start_kernel
loop	lda start_kernel
	beq loop
	mva #0 start_kernel
	jsr kernel

	lda next_stone
	bne loop
loop3	lda 53770
	and #31
	tax
	lda vram+4,x
	bne loop3
	lda #3
	sta vram+4,x
	lda #12
	sta vram+44,x
	ldx level
	lda nexttab,x
	sta next_stone
	lda end_flag
	bne endgame
	lda next_level
	bne loop
	inc level
	jsr set_skyscraper
	jmp main
endgame	jmp start_game

dli		pha
	lda var1
	sta wsync
	sta $d01a
	lda #15
	sta $d016
	lda #<dli1
	sta dliv
	lda #>dli1
	sta dliv+1
	pla
	rti		

;**** rasterinterrupt for the main game screen		
dli1	pha
	txa
	pha
	tya
	pha
	ldy #8
	lda interlace	;check for interlace and delay one scanline
	bne dli_loop
:6		sta wsync
dli_loop lda var1		
	tax
	add #$f0
	sta var1
:12		sta wsync
	sta $d01a
	stx wsync
	stx $d01a
	sta wsync
	sta $d01a
	dey
	bne dli_loop
	mva #$a8 wsync
	sta $d01a
	sta start_kernel
	pla
	tay
	pla
	tax
	pla
	rti				
	
wait_vbl lda #1
	sta vbl_flag	
wait_vbl_loop	lda vbl_flag
	bne wait_vbl_loop
	rts

;***** main-kernel
;***** runs through vram and moves meteors down
;***** and turn on/off the lights in the skyscrapers

kernel ldx #24
	mwa #vram scr_pointer
kernel_loop ldy #39
kernel_loop1 lda (scr_pointer),y
	beq	kernel_loop2			;skip if its the sky
	bmi	kernel_loop2			;skip if its a skyscraper (char>128)
	add #1
	cmp #11					;maximum reached? then move sprite down		
	bne kernel_loop4
	lda #0
	sta (scr_pointer),y			;whipe top of sprite
	sty save_y
	tya
	add #80
	tay
	lda (scr_pointer),y
	bpl kernel_loop5			;hit skyscraper? trigger sound
	lda #0
	sta (scr_pointer),y
	tya
	sub #40
	tay

	lda #0
	sta (scr_pointer),y

kernel_loop99	beq kernel_loop4
kernel_loop5 tya
	sub #40
	tay		
	lda #3
kernel_loop6		sta (scr_pointer),y
	tya
	add #40
	tay
	lda #12
	sta (scr_pointer),y
	ldy save_y
	bne kernel_loop2
kernel_loop4 sta (scr_pointer),y
kernel_loop2 dey
	bne kernel_loop1
	lda scr_pointer
	add #40
	sta scr_pointer
	bcc kernel_loop3
	inc scr_pointer+1
kernel_loop3 dex
	bne kernel_loop
	rts

;***** init pm-grafics
pm_init	ldx #0
	txa
pm_init_loop0 sta p0,x
	sta p0+256,x
	sta p0+512,x
	sta p0+768,x
	inx
	bne pm_init_loop0
	stx 53257
	stx 53258
	stx 53259
	lda #$c0
pm_init_loop2 sta p0+256+$20,x
	inx
	cpx #176
	bcc pm_init_loop2
	lda #192
	sta 53251
	lda #15
	sta $d015
	sta $d012
	lda #$34
	sta $d013
	lda #48
	sta 53248
	sta car_pos_x
	sta 53249
	lda #3
	sta 53277
	lda #1
	sta 53256
	lda #>sprites
	sta 54279	
set_car ldy #0
	ldx	car_dir		;which car sprite? 0,11 ofset
pm_init_loop1 lda car_r,x
	sta p0+217,y
	iny
	inx
	cpy #10
	bcc pm_init_loop1
	rts

set_man	ldy #0
	ldx #0
set_man_loop	lda sprite,x
	sta p3+216,y
	inx
	iny
	cpy #11
	bcc set_man_loop
	rts
	
;***** sets the 2 skyscrapers
set_skyscraper mwa #vram+80 skyv
	ldx #9				;set 10 lines
	mva #32 var2
set_skyscraper_loop ldy #39
set_skyscraper_loop0 lda skyscraper_data,y
	beq set_skyscraper_loop3			;space?
	lda 53770
	and #1
	add #160
set_skyscraper_loop3		sta (skyv),y-
	bpl set_skyscraper_loop0	
	lda skyv			;move screen pointer one line down
	add #40
	sta skyv
	bcc set_skyscraper_loop1
	inc skyv+1
set_skyscraper_loop1 dex
	bne set_skyscraper_loop
	rts	

;*****  Add A to a BCD number
add_score
	sed
	clc
_bcdc
	adc	score,x
	sta score,x
add_score2 lda #$00
	inx
	bcs _bcdc
	cld
	rts

;-----  Write two digits BCD a to sprite at y
write_bcd
	pha		;1st digit
	lsr @
	lsr @
	lsr @
	lsr @
	sty save_y	;save y-reg
	jsr WriteNumber
	pla		;2nd digit
	and #$0f
	ldy save_y	
	iny		;next position
WriteNumber
	clc
	adc #48		;offset for font
_wrlp
	sta status_line,y
	iny
	rts		
	
;***** puts whole score on screen
write_score ldy #3
	lda score+2
	jsr write_bcd	;1000-9999
	lda score+1
	jsr write_bcd	;100-999
	lda score
	jsr write_bcd	;00-99
	rts

;***** move car
move_car jsr set_car
	lda end_flag
	bne move_car_end 
	lda car_pos_x
	sta 53248	
	lda stick0
	and #$f8	;right?
	bne move_car2
	lda #0
	sta car_dir
	lda car_pos_x
	cmp #$c0
	bcs move_car_end
	inc car_pos_x;move car one pixel to the right
	rts
move_car2 lda stick0	
	and #244;left?
	bne move_car_end
	lda #11
	sta car_dir
	lda car_pos_x
	cmp #$30
	bcc move_car_end
	dec car_pos_x
move_car_end rts		
	
;***** time-out bar
;***** a=0 - set & init bar
;***** a<>0 - count down depending on level

set_timeout_bar ldx timer_pos+1
	lda #0
	sta p0+256+$20,x
	lda timer_pos
	add	timer_add
	sta timer_pos
	lda timer_pos+1
	adc timer_add+1
	sta timer_pos+1
	rts

;***** checks if player hits an asteroid or
;***** if he picked up the man
check_collision	lda colp0pl			;checks colission with man
	beq check0
	sta 53251
	sta pickup_flag
check0	lda car_pos_x;left screen reached with man?		
	cmp #$30
	bcs check1
	lda pickup_flag
	beq check1
	ldx level
	lda scoretab,x
	ldx #1
	jsr add_score
	jsr write_score
	lda #0
	sta pickup_flag
	lda #192
	sta 53251
	dec next_level;decress how many men to pick up for next level
check1	lda colp0pf	;checks collision with asteroid
	beq check2
	sta end_flag
check2	sta hitclr	;clears collision registers
	rts

;----- Atari specific code
switch_off_os_rom   sei			 ;stop interrups
	mva #0 ^4e	  ;stop all interrupts
	mva #$fe ^31;switch off ROM to get 16k more ram
	mwa #nmi $fffa;new NMI handler
	mwa #nmi $fffe
	mwa #dli dliv	
	mva #$c0 ^4e;switch on NMI+VBL again
	rts
; NMI routine
; ^4f==#$5f if VBLKI
; ^4f==#$9f if DLI
nmi		bit	^4f
	bpl	sys_vbl
; DLI routine, e.g.
;	pha
   	jmp (dliv)
;	pla
;	rti

; VBL routine, e.g.
sys_vbl	pha
	txa:pha
	tya:pha
	lda $d300		   ;prepare joystick
	and #$0f
	sta stick0
	lda #8+$80
	sta var1
	lda interlace
	eor #1
	sta interlace
	dec vbl_flag
	lda #<dli
	sta dliv
	lda #>dli
	sta dliv+1
	jsr vbl
	pla:tay
	pla:tax
	pla
	rti

vbl		mva #$88 $d01a
	jsr check_collision
	jsr move_car
	jsr set_man
	jsr set_timeout_bar
;		jsr sound_engine
	lda next_stone
	beq vbl0
	dec next_stone
vbl0	dec flash_counter
	bne vbl_end
	lda 53770
	and #15
	sta $d017
	lda 53770
	and #15
	sta $d016
vbl_end	rts

sound_engine jsr do_siren
	rts
	
do_siren dec siren_delay
	beq do_siren0
	rts
do_siren0 lda #32
	sta siren_delay	
	lda siren_mode
	eor #1
	sta siren_mode
	beq do_siren1
	lda #100
	sta soundf0+2
	lda #$af
	sta soundc0+2
	rts
do_siren1 lda #160
	sta soundf0+2
	lda #$af
	sta soundc0+2
	rts
	org start+$800
skyscraper_data dta d"		!!!!!!!!		!!!!!!!!		 "
status_line dta d"CDEPPPPPP FCDEPPPPPP"
dlist dta $f0,$c6,a(status_line),$70
dta $45,a(vram)
dta 5,5,5,5,5,5,5,5,5,5,5,5
dta $41,a(dlist)

;***** level data (1-10)

mantab	dta 2,4,6,10,14,18,26,34,42,50
scoretab dta 2,2,2,4,4,4,8,8,8,10;*100
;NTSC tab * 60, PAL * 50
timetabl dta <360,<480,<540,<600,<850,<1080,<1320,<1560,<1680,<1800
timetabh dta >360,>480,>540,>600,>850,>1080,>1320,>1560,>1680,>1800
nexttab	dta 120,40,30,20,15,12,10,9,8,7



;**** custom font
	org font+$18
		
	dta %00111100;3
	dta %11111111
	dta %11111111
	dta %00111100
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000

	dta %00000000;4
	dta %00111100
	dta %11111111
	dta %11111111
	dta %00111100
	dta %00000000
	dta %00000000
	dta %00000000

	dta %00000000;5
	dta %00000000
	dta %00111100
	dta %11111111
	dta %11111111
	dta %00111100
	dta %00000000
	dta %00000000

	dta %00000000;6
	dta %00000000
	dta %00000000
	dta %00111100
	dta %11111111
	dta %11111111
	dta %00111100
	dta %00000000

	dta %00000000;7
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00111100
	dta %11111111
	dta %11111111
	dta %00111100

	dta %00000000;8
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00111100
	dta %11111111
	dta %11111111
	
	dta %00000000;9
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00111100
	dta %11111111
	
	dta %00000000;10
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00111100
	
	dta %00000000;11 (buffer)
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	

;2nd half
	dta %00000000;12
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	
	dta %00000000;13
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	
	dta %00000000;14
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	
	dta %00000000;15
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000

	
	dta %00111100;16
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	
	dta %11111111;17
	dta %00111100
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	
	dta %11111111;18
	dta %11111111
	dta %00111100
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000

	dta %00111100;19
	dta %11111111
	dta %11111111
	dta %00111100
	dta %00000000
	dta %00000000
	dta %00000000
	dta %00000000
			
	org $8000+32*8
	dta %11111111	;@
	dta %11010111
	dta %11010111
	dta %11111111
	dta %11111111
	dta %11101011
	dta %11101011
	dta %11111111
	
	dta %11111111	;A
	dta %11101011
	dta %11101011
	dta %11111111
	dta %11111111
	dta %11010111
	dta %11010111
	dta %11111111

	dta %11111111	;B
	dta %11111111
	dta %11111111
	dta %11111111
	dta %11111111
	dta %11111111
	dta %11111111
	dta %11111111

	dta %00000000	;C
	dta %11101110
	dta %10001000
	dta %11101000
	dta %00101000
	dta %00101000
	dta %11101110
	dta %00000000
	
	dta %00000000	;D
	dta %11101110
	dta %10101010
	dta %10101100
	dta %10101100
	dta %10101010
	dta %11101010
	dta %00000000
	
	dta %00000000	;E
	dta %11100000
	dta %10000000
	dta %11000100
	dta %10000000
	dta %10000100
	dta %11100000
	dta %00000000
	
	dta %00000000	;F
	dta %10100100
	dta %10100100
	dta %11100100
	dta %10100100
	dta %10100100
	dta %10100100
	dta %00000000

;***** man sprite
	
sprite	dta %10001000
	dta %11011100
	dta %10011100	
	dta %11001000
	dta %01111110
	dta %00011101
	dta %00011101
	dta %00011100
	dta %00011100
	dta %00010100
	dta %00110110		

car_r	dta %00100000
	dta %11110000
	dta %11110000
	dta %11110000
	dta %11101000
	dta %11111000
	dta %11111111
	dta %11111111
	dta %11111111
	dta %01000010
	dta 0

car_l	dta %00000100
	dta %00001111
	dta %00001111
	dta %00001111
	dta	%00010111
	dta %00011111
	dta %11111111
	dta %11111111
	dta %11111111
	dta %01000010
	
							
	run start

Link to comment
Share on other sites

start_game lda 53279
	cmp #6; change to lsr a
	bne start_game; change to bcs ...

 

Saved one byte!!!

 

I've noticed a few add/subtract ops. In cases where you know that the carry will be clear or set, you can save another byte by ADC # <number-1>,SBC # <number-1> etc.

 

A reasonable amount of inline code there that just inits HW regs, RAM variables etc. Maybe make a subroutine that does a table lookup and does the stores. The table layout would be:

 

.word ADDRESS

.byte VALUE

 

ADDRESS=0 means end of table.

 

$D40E (NMIEN) always reads as $FF, so an ASL $D40E instruction would save 2 bytes each time instead of LDA #$C0 , STA $D40E.

Edited by Rybags
Link to comment
Share on other sites

You could just LSR $D01F but it's not recommended if the OS VB routine is running since it stores 8 every VBI.

 

By doing a LSR, you would generate a 50 Hz pulse wave through the keyboard speaker.

 

 

What about the bulk-store routine?

 

bulk_store
; on entry, X= index into address, data table
; each entry = .WORD ADDRESS
; and .BYTE DATA
ldy #0
loop
lda store_table,X
sta $FE
lda store_table+1,X
sta $FF
ora $FE
beq finished
lda store_table+1,X
sta ($FE),y
inx
inx 
inx 
jmp loop
finished
rts
;
; example table
;
store_table
.WORD $D01A
.BYTE $74
.WORD $D40E
.BYTE $C0
.WORD $230
.BYTE <dlist
.word $231
.byte >dlist
.byte 0; end of table

 

Using such a technique, you'd probably need about 25 or more table entries, or multiple calls to the same entries before you started saving memory.

Edited by Rybags
Link to comment
Share on other sites

I'll take a stab at some 6502 optimization, :lol:.

		org $4000
start	jsr set_skyscraper

font_copy	ldx #0
font_copy_loop lda $e080,x
	sta font+48*8,x
	inx
	cpx #80
	bne font_copy_loop

If this loop can count down you'd save two bytes here:

font_copy
  ldx #79
font_copy_loop
  lda $e080,X
  sta font+48*8,X
  dex
  bpl font_copy_loop

Next...

		jsr switch_off_os_rom
	jsr wait_vbl
	jsr pm_init
	mva #$80 $d409
	mva #62 $d400
	mwa #dlist dlistv
	mva #4 $d016
	mva #8 $d017
	mva #2 $d019

I think you mentioned this already, but combining all your memory/variable initialization into a loop with a table would probably save few bytes. Might be tricky since, unlike the 2600, all your RAM isn't in the zero page! :lol:

start_game lda 53279
	cmp #6
	bne start_game
	mva #0 interlace
	sta score

Could replace this with:

start_game
  lda 53279
  eor #6
  bne start_game
  sta interlace			  ;assuming that the 'MVA' pseudo-op is what I think it is (lda, sta)
  sta score
 ;--etc.

Saves two bytes. Learned that trick from TJ. ;)

		sta score+1
	sta score+2
	sta level
	sta end_flag			
	sta car_dir
	jsr write_score
	mva #8 var1
	sta hitclr
	mva #$30 car_pos_x
	
main	ldx level
	lda timetabl,x
	sta timer_add
	lda timetabh,x
	sta timer_add+1
	lda mantab,x
	sta next_level

;loop99	jmp loop99
	mva #0 start_kernel
loop	lda start_kernel
	beq loop
	mva #0 start_kernel

Am I missing something here? What is the purpose of this code (starting one line above the "loop" label)?

		jsr kernel

Looks like this subroutine is called only once. Eliminate the 'JSR' and move the whole "kernel" subroutine inline right here; saves 4 bytes from losing the JSR call and the RTS.

		lda next_stone
	bne loop
loop3	lda 53770
	and #31
	tax
	lda vram+4,x
	bne loop3
	lda #3
	sta vram+4,x
	lda #12
	sta vram+44,x
	ldx level
	lda nexttab,x
	sta next_stone
	lda end_flag
	bne endgame
	lda next_level
	bne loop
	inc level
	jsr set_skyscraper
	jmp main
endgame	jmp start_game

dli		pha
	lda var1
	sta wsync
	sta $d01a
	lda #15
	sta $d016
	lda #<dli1
	sta dliv
	lda #>dli1
	sta dliv+1
	pla
	rti		

I'm not real familiar with how DLIs work, but if you put all your DLI routines in the same page* then can't you just set the high byte of dliv once and then leave it alone thereafter? Save you 5 bytes, at least, from not having to lda #imm sta dliv+1 here.

*Or at least the first instruction of every DLI routine.

;**** rasterinterrupt for the main game screen		
dli1	pha
	txa
	pha
	tya
	pha
	ldy #8
	lda interlace;check for interlace and delay one scanline
	bne dli_loop
:6		sta wsync
dli_loop lda var1		
	tax
	add #$f0

I assume the 'ADD' pseudo-op code translates to: clc adc #imm.

If the carry is known then you can lose the CLC opcode and save a byte. Might not work here, though.

 

Okay, that's all for now. Hope that helps. :)

Link to comment
Share on other sites

Could optimize that a little...

bulk_store
; on entry, X= index into address, data table
; each entry = .WORD ADDRESS
; and .BYTE DATA
  ldy #0
  ldx #NUMVALUES*3  ;assuming you don't have more than 85 values to initialize!
loop
  lda store_table-3,X
  sta $FE
  lda store_table-2,X
  sta $FF
  lda store_table-1,X
  sta ($FE),y
  dex
  dex
  dex
  bne loop
finished
  rts
;
; example table
;
store_table
.WORD $D01A
.BYTE $74
.WORD $D40E
.BYTE $C0
.WORD $230
.BYTE <dlist
.word $231
.byte >dlist

Link to comment
Share on other sites

thanks guys... some of vdub's optimisations are knew by me (of course... ;)) but implemented or converted when the game is done or when it is really needed (f.e. loops counting downwards etc) but i assume that i am heading for thr 1k entry so i should try to do that...

 

but there are some really nice tricks which i havent come over after more than 20 yeards of 6502 coding... you never finish to learn... :)

 

but nobody went over THE standard 2600 optimisation... draw your players in reverse order... ;) which again i havent yet done.

 

so i'll go through the code now and implement some of it...

 

in the end i am gonna put subroutines right after each others to save the JSR...and the DLI trick is correct as well... you don't need to store the highbyte if on same page... thank 800xl for his plenty of ram.... ;)

Link to comment
Share on other sites

Join the conversation

You can post now and register later. If you have an account, sign in now to post with your account.
Note: Your post will require moderator approval before it will be visible.

Guest
Reply to this topic...

×   Pasted as rich text.   Paste as plain text instead

  Only 75 emoji are allowed.

×   Your link has been automatically embedded.   Display as a link instead

×   Your previous content has been restored.   Clear editor

×   You cannot paste images directly. Upload or insert images from URL.

Loading...
  • Recently Browsing   0 members

    • No registered users viewing this page.
×
×
  • Create New...