Jump to content
IGNORED

Moving a missile


Recommended Posts

I'm trying to get a missile to fire from the player 0 when the fire button is pressed. I managed to get the missile to appear when the player presses the fire button, but it doesn't appear where expected at the front of player 0. Additionally if player 0 moves the missile doesn't fire at player 0's new position. Any ideas?

 

	; First we have to tell DASM that we're 
; coding to the 6502:

	processor 6502

; Then we have to include the "vcs.h" file
; that includes all the "convenience names"
; for all the special atari memory locations...

	include "vcs.h"

	include "macro.h"

;**************************************************************************

	SEG.U vars; tells dasm that the proceding instructions are variable declarations
			
	ORG $80; tells dasm to start placing our variables in memory location 0080

player0x = $80; player0's x position

player0y = $81; player0's y position

shotfired = $82

visibleplayer0line = $83; current visible line for player 0

player0buffer = $84; player buffer for holding the line to draw for the player graphic

missile0x = $85; missile 0's x position

missile0y = $86; missile 0's y position

visiblemissileline = $87; line where missile is drawn

lives = $88; player lives

score = $89; game score

	SEG code

; tell DASM where in the memory to place
; all the code that follows...$F000 is the preferred
; spot where it goes to make an atari program

	ORG $F000

; we'll call the start of our program "Start".
Start

	SEI	; Disable Any Interrupts
	CLD	  ; Clear BCD math bit.
	LDX #$FF; put X to the top...
	TXS	; ...and use it reset the stack pointer

; Clear RAM and all TIA registers

	lda #0	;Put Zero into A, X is at $FF

Clear		   sta 0,x	;Now, this doesn't mean what you think...

	dex	;decrement X (decrease X by one)

	bne Clear;if the last command resulted in something 
		 ;that's "N"ot "Equal" to Zero, branch back
		 ;to "Clear"

;---------------------
; One Time Initiations

	lda #$FA

	sta COLUBK; set the background color to sandy brown

	lda #$04

	sta COLUP0; set the player color to silver

	lda #$B8

	sta COLUPF; set the playfield color to ooze green

;---------------------
; Start New Game

StartNewGame	lda #105

	sta player0x; player0's initial x position

	lda #40

	sta player0y; player0's initial y position

	lda #0

	sta shotfired; set shotfired inital value to 0

	lda #0

	sta missile0x; missile 0's initial x position

	lda #0

	sta missile0y; missile 0's initial y position

	lda #3

	sta lives; start the player with 3 lives

	lda #0

	sta score; set high bit of score inital value to 0

	lda #0

	sta score+1; set nibble bit of score inital value to 0

	lda #0

	sta score+2; low bit of score inital value to 0

GameLoop

;*********************** VERTICAL SYNC HANDLER

	lda  #2

	sta VSYNC; Sync it up you damn dirty television!
		; and that vsync on needs to be held for three scanlines...
		; count with me here,
	sta WSYNC; one... (our program waited for the first scanline to finish...)

	sta WSYNC; two...

	sta WSYNC; three...

	lda  #43;load 43 (decimal) in the accumulator

	sta  TIM64T;and store that in the timer

	lda #0	; Zero out the VSYNC
	sta  VSYNC ; cause that time is over

;*********************** Joystick Input
; Here we check for left and right
; joystick input

	lda #%01000000; a 0 in bit D6 means the joystick was pushed left

	bit SWCHA; was the joystick moved left?

	bne SkipPlayer0MoveLeft; if bit D6 isn't equal to 0 then jump to SkipPlayer0MoveLeft

	dec player0x; otherwise the player moved the joystick left so deincrement the players position by one

SkipPlayer0MoveLeft

	lda #%10000000; a 0 in bit D7 means the joystick was pushed right

	bit SWCHA ; was the joystick moved right?

	bne SkipPlayer0MoveRight;if bit D6 isn't equal to 0 then jump to SkipPlayer0MoveRight

	inc player0x;otherwise the player moved the joystick right so increment the players position by one

SkipPlayer0MoveRight

	ldx player0x; load the players position into the x register

	jsr PositionSprite; jump to our Position Sprite Subroutine to position the player

	lda #0		; zero out the buffer

	sta player0buffer; just in case

	lda INPT4; read button input

	bmi ButtonNotPressed; skip if button not pressed

	lda #1	; must be pressed, set accumulator to 1 (true)

	sta shotfired; shotFired to true from value in acumulator

	lda player0x; load player 0's x position

	sta missile0x; and set it to the missile 0's x position

	lda player0y; load player 0's y position

	sta missile0y; and set it to missile 0's y position

	lda #2	; set the acumulator to 2

	sed	; set decimal mode

	clc	; clear carry status

	adc missile0y; set missile 0's position just above player 0

	cld	; clear decimal mode 

ButtonNotPressed


;*********************** VERTICAL BLANK WAIT-ER
WaitForVblankEnd

	lda INTIM;load timer...

	BNE WaitForVblankEnd;killing time if the timer's not yet zero

	ldy #191 ;Y is going to hold how many lines we have to do
		;...we're going to count scanlines here. theoretically
		; since this example is ass simple, we could just repeat
		; the timer trick, but often its important to know 
		; just what scan line we're at.

	sta WSYNC;We do a WSYNC just before that so we don't turn on

	sta VBLANK;End the VBLANK period with the zero

;*********************** Scan line Loop
ScanLoop

	sta WSYNC ;Wait for the previous line to finish

	lda player0buffer;buffer was set during last scanline

	sta GRP0		;put it as graphics now

	cpy player0y; compare the player's y position

	bne SkipActivatePlayer0; if it isn't 0 then jump to SkipActivePlayer0

	lda #5	; otherwise load our accumulatior with the number of lines to draw

	sta visibleplayer0line; and store it 

SkipActivatePlayer0

;set player buffer to all zeros for this line, and then see if 
;we need to load it with graphic data

	lda #0		

	sta player0buffer  ;set buffer, not GRP0

;if the VisiblePlayerLine is non zero,
;we're drawing it next line

	ldx visibleplayer0line;check the visible player line...

	beq FinishPlayer;skip the drawing if its zero...

	lda player0-1,X	;otherwise, load the correct line from player0
			;section below... it's off by 1 though, since at zero
			;we stop drawing
	sta player0buffer;put that line as player graphic for the next line

	dec visibleplayer0line;and decrement the line count

FinishPlayer

; here the idea is that VisibleMissileLine
; is zero if the line isn't being drawn now,
; otherwise it's however many lines we have to go

CheckActivateMissile

	cpy missile0y

	bne SkipActivateMissile

	lda #8

	sta visiblemissileline

SkipActivateMissile

;turn missile off then see if it's turned on

	lda #0	

	sta ENAM0

;if the VisibleMissileLine is non zero,
;we're drawing it

	lda visiblemissileline

	beq FinishMissile

	lda #2		

	sta ENAM0

	dec visiblemissileline

	inc missile0y

FinishMissile

	dey	;subtract one off the line counter thingy

	bne ScanLoop;and repeat if we're not finished with all the scanlines.

	lda #2	;#2 for the VBLANK...

	sta WSYNC  ;Finish this final scanline.

	sta VBLANK ; Make TIA output invisible for the overscan, 
		; (and keep it that way for the vsync and vblank)

;***************************** OVERSCAN CALCULATIONS
;I'm just gonna count off the 30 lines of the overscan.
;You could do more program code if you wanted to.

	ldx #30	;store 30

OverScanWait

	sta WSYNC

	dex

	bne OverScanWait

	jmp  GameLoop	 ;Continue this loop forver! Back to the code for the vsync etc

Divide15

.POS	SET 0			; start our counter at 0

	REPEAT 256	; repeat this loop 256 times

	.byte (.POS / 15) + 1; put that counter value / 15 in the ROM

.POS	SET .POS + 1		; increment our counter by one

	REPEND		; repeat the loop if neccessary

PositionSprite

	sta WSYNC	; wait for vsync

; Pass X register holding desired X position of sprite!

	lda Divide15,x; xPosition / 15

	tax	; transfer the value in the accumulator to the x register

SimpleLoop	dex	; deincrement x by 1

	bne SimpleLoop; continue looping if the x register isn't 0

	sta RESP0; start drawing the sprite

	rts	; return from the subroutine

	; here's the actual player0 graphic

player0
		.byte #%00011000
		.byte #%00111100
		.byte #%11111111
		.byte #%00111100
		.byte #%00011000

update_low_score_digits

	sed 	; set decimal mode

	clc 	; clear carry status

	adc score ; add accumulator to score's low digits w/carry.

	sta score; store the updated low digits.

;NOTE: Here's where a triple-NOP comes into play.  We need
;a seperate entrypoint to this subroutine for cases where the
;low digits are ignored (like adding 100, for example).  But
;carry status and BCD mode need to have been setup.  So,
;place the triple-NOP opcode here to skip over them...
;with A reset at zero so that only carry affects the score:

	lda #0 	; reset the accumulator...

	.byte $0C ; ...and skip over the next 2 bytes

update_middle_score_digits

	sed 	; set decimal mode

	clc; clear carry status

	adc score+1 ; add accumulator to score's middle digits w/carry.

	sta score+1 ; store the updated middle digits

;Here we do the same thing (in case the game needs to add 10,000...
;or 100,000 increments to a score (ignoring all the lower ones)
;Again, A is reset at zero so that only carry affects the score:

	lda #0	; reset the accumulator...

	.byte $0C; ...and skip over the next 2 bytes

update_high_score_digits

	sed	; set decimal mode

	clc	; clear carry status

	adc score+1; add accumulator to score's high digits w/carry.

	sta score+2; store the last 2 digits

;With the score updated, clear BCD mode and exit via RTS:

	cld	; clear decimal mode

	rts	; and return to the program line that called this routine.

;*************************************************************************
; Interrupt Vectors

	ORG $FFFA

InterruptVectors

	.word Start		 ; NMI

	.word Start		 ; RESET

	.word Start		 ; IRQ

	END

Link to comment
Share on other sites

I'm not up to scratch on the 2600, but...

  lda player0y; load player 0's y position
 sta missile0y; and set it to missile 0's y position
 lda #2   ; set the acumulator to 2
 sed   ; set decimal mode
 clc   ; clear carry status
 adc missile0y; set missile 0's position just above player 0
 cld   ; clear decimal mode 
ButtonNotPressed
  ;*********************** VERTICAL BLANK WAIT-ER
WaitForVblankEnd
		lda INTIM;load timer...

 

Why are you using Decimal mode for calculating Y postition?

Also, you're doing the add, but not storing it anywhere.

 

Another unrelated hint... with flags, rather than testing them by doing a LDA... BEQ - it's useful to just use the top 2 bits of a byte to signify things, then you can just test with the BIT instruction, without having to lose contents of a register.

Link to comment
Share on other sites

Thanks, i fixed the code and now i got it to appear above the player sprite. However for some reason it doesn't fire from player 0's x position and instead fires from the same exact location every time. I have posted the code for reference.

 

	; First we have to tell DASM that we're 
; coding to the 6502:

	processor 6502

; Then we have to include the "vcs.h" file
; that includes all the "convenience names"
; for all the special atari memory locations...

	include "vcs.h"

	include "macro.h"

;**************************************************************************

	SEG.U vars; tells dasm that the proceding instructions are variable declarations
			
	ORG $80; tells dasm to start placing our variables in memory location 0080

player0x = $80; player0's x position

player0y = $81; player0's y position

visibleplayer0line = $82; current visible line for player 0

player0buffer = $83; player buffer for holding the line to draw for the player graphic

missile0x = $84; missile 0's x position

missile0y = $85; missile 0's y position

visiblemissile0line = $86; line where missile is drawn

lives = $87; player lives

score = $88; game score

	SEG code

; tell DASM where in the memory to place
; all the code that follows...$F000 is the preferred
; spot where it goes to make an atari program

	ORG $F000

; we'll call the start of our program "Start".
Start

	SEI	; Disable Any Interrupts
	CLD	  ; Clear BCD math bit.
	LDX #$FF; put X to the top...
	TXS	; ...and use it reset the stack pointer

; Clear RAM and all TIA registers

	lda #0	;Put Zero into A, X is at $FF

Clear		   sta 0,x	;Now, this doesn't mean what you think...

	dex	;decrement X (decrease X by one)

	bne Clear;if the last command resulted in something 
		 ;that's "N"ot "Equal" to Zero, branch back
		 ;to "Clear"

;---------------------
; One Time Initiations

	lda #$FA

	sta COLUBK; set the background color to sandy brown

	lda #$04

	sta COLUP0; set the player color to silver

	lda #$B8

	sta COLUPF; set the playfield color to ooze green

;---------------------
; Start New Game

StartNewGame	lda #105

	sta player0x; player0's initial x position

	lda #40

	sta player0y; player0's initial y position

	lda #0

	sta missile0x; missile 0's initial x position

	lda #0

	sta missile0y; missile 0's initial y position

	lda #3

	sta lives; start the player with 3 lives

	lda #0

	sta score; set high bit of score inital value to 0

	lda #0

	sta score+1; set nibble bit of score inital value to 0

	lda #0

	sta score+2; low bit of score inital value to 0

GameLoop

;*********************** VERTICAL SYNC HANDLER

	lda  #2

	sta VSYNC; Sync it up you damn dirty television!
		; and that vsync on needs to be held for three scanlines...
		; count with me here,
	sta WSYNC; one... (our program waited for the first scanline to finish...)

	sta WSYNC; two...

	sta WSYNC; three...

	lda  #43;load 43 (decimal) in the accumulator

	sta  TIM64T;and store that in the timer

	lda #0	; Zero out the VSYNC
	sta  VSYNC ; cause that time is over

;*********************** Joystick Input
; Here we check for left and right
; joystick input

	lda #%01000000; a 0 in bit D6 means the joystick was pushed left

	bit SWCHA; was the joystick moved left?

	bne SkipPlayer0MoveLeft; if bit D6 isn't equal to 0 then jump to SkipPlayer0MoveLeft

	dec player0x; otherwise the player moved the joystick left so deincrement the players position by one

SkipPlayer0MoveLeft

	lda #%10000000; a 0 in bit D7 means the joystick was pushed right

	bit SWCHA ; was the joystick moved right?

	bne SkipPlayer0MoveRight;if bit D6 isn't equal to 0 then jump to SkipPlayer0MoveRight

	inc player0x;otherwise the player moved the joystick right so increment the players position by one

SkipPlayer0MoveRight

	ldx player0x; load the players position into the x register

	jsr PositionSprite; jump to our Position Sprite Subroutine to position the player

	lda #0		; zero out the buffer

	sta player0buffer; just in case

	lda INPT4; read button input

	bmi ButtonNotPressed; skip if button not pressed

	lda player0x; load player 0's x position

	sta missile0x; and set it to the missile 0's x position

	lda player0y; load player 0's y position

	sta missile0y; and set it to missile 0's y position

	lda #8	; set the acumulator to 8

	clc	; clear carry status

	adc missile0y; add 2 to missile 0's y position so it's above player 0

	sta missile0y; and set it to missile 0's y position

ButtonNotPressed


;*********************** VERTICAL BLANK WAIT-ER
WaitForVblankEnd

	lda INTIM;load timer...

	BNE WaitForVblankEnd;killing time if the timer's not yet zero

	ldy #191 ;Y is going to hold how many lines we have to do
		;...we're going to count scanlines here. theoretically
		; since this example is ass simple, we could just repeat
		; the timer trick, but often its important to know 
		; just what scan line we're at.

	sta WSYNC;We do a WSYNC just before that so we don't turn on

	sta VBLANK;End the VBLANK period with the zero

;*********************** Scan line Loop
ScanLoop

	sta WSYNC ;Wait for the previous line to finish

	lda player0buffer;buffer was set during last scanline

	sta GRP0		;put it as graphics now

	cpy player0y; compare the player's y position

	bne SkipActivatePlayer0; if it isn't 0 then jump to SkipActivePlayer0

	lda #5	; otherwise load our accumulatior with the number of lines to draw

	sta visibleplayer0line; and store it 

SkipActivatePlayer0

;set player buffer to all zeros for this line, and then see if 
;we need to load it with graphic data

	lda #0		

	sta player0buffer  ;set buffer, not GRP0

;if the VisiblePlayerLine is non zero,
;we're drawing it next line

	ldx visibleplayer0line;check the visible player line...

	beq FinishPlayer;skip the drawing if its zero...

	lda player0-1,X	;otherwise, load the correct line from player0
			;section below... it's off by 1 though, since at zero
			;we stop drawing
	sta player0buffer;put that line as player graphic for the next line

	dec visibleplayer0line;and decrement the line count

FinishPlayer

; here the idea is that visiblemissile0line
; is zero if the line isn't being drawn now,
; otherwise it's however many lines we have to go

CheckActivateMissile

	cpy missile0y; is missile 0's y position the same as the current scanline?

	bne SkipActivateMissile; if it isn't then don't set missle 0's visible lines

	lda #8		; otherwise set the missiles visible lines to 8

	sta visiblemissile0line; and store it in the visiblemissileline

SkipActivateMissile

;turn missile off then see if it's turned on

	lda #0

	sta ENAM0; disable the missile

;if the visiblemissile0line is non zero,
;we're drawing it

	lda visiblemissile0line; if the visiblemissle line is zero

	beq FinishMissile; don't draw the missile

	lda #2		; otherwise set the accumulator to 2		

	sta ENAM0	; and draw the missile

	dec visiblemissile0line; and decrement the visiblemissileline by 1

	inc missile0y	; increment missle 0's y position by 1

FinishMissile

	dey	;subtract one off the line counter thingy

	bne ScanLoop;and repeat if we're not finished with all the scanlines.

	lda #2	;#2 for the VBLANK...

	sta WSYNC  ;Finish this final scanline.

	sta VBLANK ; Make TIA output invisible for the overscan, 
		; (and keep it that way for the vsync and vblank)

;***************************** OVERSCAN CALCULATIONS
;I'm just gonna count off the 30 lines of the overscan.
;You could do more program code if you wanted to.

	ldx #30	;store 30

OverScanWait

	sta WSYNC

	dex

	bne OverScanWait

	jmp  GameLoop	 ;Continue this loop forver! Back to the code for the vsync etc

Divide15

.POS	SET 0			; start our counter at 0

	REPEAT 256	; repeat this loop 256 times

	.byte (.POS / 15) + 1; put that counter value / 15 in the ROM

.POS	SET .POS + 1		; increment our counter by one

	REPEND		; repeat the loop if neccessary

PositionSprite

	sta WSYNC	; wait for vsync

; Pass X register holding desired X position of sprite!

	lda Divide15,x; xPosition / 15

	tax	; transfer the value in the accumulator to the x register

SimpleLoop	dex	; deincrement x by 1

	bne SimpleLoop; continue looping if the x register isn't 0

	sta RESP0; start drawing the sprite

	rts	; return from the subroutine

	; here's the actual player0 graphic

player0
		.byte #%00011000
		.byte #%00111100
		.byte #%11111111
		.byte #%00111100
		.byte #%00011000

update_low_score_digits

	sed 	; set decimal mode

	clc 	; clear carry status

	adc score ; add accumulator to score's low digits w/carry.

	sta score; store the updated low digits.

;NOTE: Here's where a triple-NOP comes into play.  We need
;a seperate entrypoint to this subroutine for cases where the
;low digits are ignored (like adding 100, for example).  But
;carry status and BCD mode need to have been setup.  So,
;place the triple-NOP opcode here to skip over them...
;with A reset at zero so that only carry affects the score:

	lda #0 	; reset the accumulator...

	.byte $0C ; ...and skip over the next 2 bytes

update_middle_score_digits

	sed 	; set decimal mode

	clc; clear carry status

	adc score+1 ; add accumulator to score's middle digits w/carry.

	sta score+1 ; store the updated middle digits

;Here we do the same thing (in case the game needs to add 10,000...
;or 100,000 increments to a score (ignoring all the lower ones)
;Again, A is reset at zero so that only carry affects the score:

	lda #0	; reset the accumulator...

	.byte $0C; ...and skip over the next 2 bytes

update_high_score_digits

	sed	; set decimal mode

	clc	; clear carry status

	adc score+1; add accumulator to score's high digits w/carry.

	sta score+2; store the last 2 digits

;With the score updated, clear BCD mode and exit via RTS:

	cld	; clear decimal mode

	rts	; and return to the program line that called this routine.

;*************************************************************************
; Interrupt Vectors

	ORG $FFFA

InterruptVectors

	.word Start		 ; NMI

	.word Start		 ; RESET

	.word Start		 ; IRQ

	END

 

Sincerely,

 

Primordial Ooze

Edited by Primordial Ooze
Link to comment
Share on other sites

Your problem is that you never reposition the missile. No matter what you store in missile x, it will never move horizontally. You should probably get write/find a universal horizontal positioning routine.

 

this is the one I use:

 

PositionSprites
	sta HMCLR
	sec
	sta WSYNC		 
PositionSpriteLoop
	sbc	#15
	bcs	PositionSpriteLoop 

	eor	#7		 
	asl
	asl
	asl
	asl			   

	sta.wx HMP0,X	 
	sta	RESP0,X   
	sta	WSYNC	  
	sta	HMOVE	 
	rts

 

all you do is load the horizontal position to the accumulator, load the sprite # in X (0 for P0, 1 for P1, 2 for M0, 3 for M1, 4 for BL), and jsr PositionSprites. it takes 2 lines, and you have to put a WSYNC write in between calls like this:

 

	lda player0x
ldx #0
jsr PositionSprites

sta WSYNC

lda missile0x
ldx #2
jsr PositionSprites

 

the WSYNC write is required because of a hardware bug of the TIA that requires a 24 cycle delay after an HMOVE before HMxx writes. It will work fine on an emulator without the WSYNC write, but there will be unpredictable results on the real thing.

Edited by Wickeycolumbus
Link to comment
Share on other sites

Thanks, but it still doesn't quite work. If you hold the fire button down and move the player towards the left after you reach the middle left you will notice missile 0 will "cave in" into player 0's sprite and if you continue moving left the missile will be almost completely merged with player 0's sprite and stops working altogether. If you move towards the right, everything works as normal. Any ideas?

 

; First we have to tell DASM that we're 
; coding to the 6502:

	processor 6502

; Then we have to include the "vcs.h" file
; that includes all the "convenience names"
; for all the special atari memory locations...

	include "vcs.h"

	include "macro.h"

;**************************************************************************

	SEG.U vars; tells dasm that the proceding instructions are variable declarations
			
	ORG $80; tells dasm to start placing our variables in memory location 0080

player0x = $80; player0's x position

player0y = $81; player0's y position

visibleplayer0line = $82; current visible line for player 0

player0buffer = $83; player buffer for holding the line to draw for the player graphic

missile0x = $84; missile 0's x position

missile0y = $85; missile 0's y position

visiblemissile0line = $86; line where missile is drawn

lives = $87; player lives

score = $88; game score

	SEG code

; tell DASM where in the memory to place
; all the code that follows...$F000 is the preferred
; spot where it goes to make an atari program

	ORG $F000

; we'll call the start of our program "Start".
Start

	SEI; Disable Any Interrupts
	CLD	; Clear BCD math bit.
	LDX #$FF; put X to the top...
	TXS; ...and use it reset the stack pointer

; Clear RAM and all TIA registers

	lda #0;Put Zero into A, X is at $FF

Clear		   sta 0,x;Now, this doesn't mean what you think...

	dex;decrement X (decrease X by one)

	bne Clear;if the last command resulted in something 
	;that's "N"ot "Equal" to Zero, branch back
	;to "Clear"

;---------------------
; One Time Initiations

	lda #$FA

	sta COLUBK; set the background color to sandy brown

	lda #$04

	sta COLUP0; set the player color to silver

	lda #$B8

	sta COLUPF; set the playfield color to ooze green

;---------------------
; Start New Game

StartNewGame	lda #105

	sta player0x; player0's initial x position

	lda #40

	sta player0y; player0's initial y position

	lda #0

	sta missile0x; missile 0's initial x position

	lda #0

	sta missile0y; missile 0's initial y position

	lda #3

	sta lives; start the player with 3 lives

	lda #0

	sta score; set high bit of score inital value to 0

	lda #0

	sta score+1; set nibble bit of score inital value to 0

	lda #0

	sta score+2; low bit of score inital value to 0

GameLoop

;*********************** VERTICAL SYNC HANDLER

	lda  #2

	sta VSYNC; Sync it up you damn dirty television!
; and that vsync on needs to be held for three scanlines...
; count with me here,
	sta WSYNC; one... (our program waited for the first scanline to finish...)

	sta WSYNC; two...

	sta WSYNC; three...

	lda  #43;load 43 (decimal) in the accumulator

	sta  TIM64T;and store that in the timer

	lda #0; Zero out the VSYNC
	sta  VSYNC; cause that time is over

;*********************** Joystick Input
; Here we check for left and right
; joystick input

	lda #%01000000; a 0 in bit D6 means the joystick was pushed left

	bit SWCHA; was the joystick moved left?

	bne SkipPlayer0MoveLeft; if bit D6 isn't equal to 0 then jump to SkipPlayer0MoveLeft

	dec player0x; otherwise the player moved the joystick left so deincrement the players position by one

SkipPlayer0MoveLeft

	lda #%10000000; a 0 in bit D7 means the joystick was pushed right

	bit SWCHA; was the joystick moved right?

	bne SkipPlayer0MoveRight;if bit D6 isn't equal to 0 then jump to SkipPlayer0MoveRight

	inc player0x;otherwise the player moved the joystick right so increment the players position by one

SkipPlayer0MoveRight

	lda player0x; load the players position into the accumulator

	ldx #0; set the sprite to be positioned as player 0

	jsr PositionSprite; jump to our Position Sprite Subroutine to position player 0

	sta WSYNC; wait for sync

	lda #0; zero out the buffer

	sta player0buffer; just in case

	lda INPT4; read button input

	bmi ButtonNotPressed; skip if button not pressed

	lda player0x; load player 0's x position

	sta missile0x; and set it to the missile 0's x position

	lda #4; set the acumulator to 4

	clc; clear carry status

	adc missile0x; add 4 to missile 0's x position so it's centered at player 0

	sta missile0x; and set it to missile 0's x position

	lda player0y; load player 0's y position

	sta missile0y; and set it to missile 0's y position

	lda #8; set the acumulator to 8

	clc; clear carry status

	adc missile0y; add 8 to missile 0's y position so it's above player 0

	sta missile0y; and set it to missile 0's y position

	lda missile0x; load missile 0's x position into the accumulator

	ldx #2; set the sprite to be positioned to missile 0

	jsr PositionSprite; jump to our Position Sprite Subroutine to position missile 0


ButtonNotPressed


;*********************** VERTICAL BLANK WAIT-ER
WaitForVblankEnd

	lda INTIM;load timer...

	BNE WaitForVblankEnd;killing time if the timer's not yet zero

	ldy #191;Y is going to hold how many lines we have to do
;...we're going to count scanlines here. theoretically
; since this example is ass simple, we could just repeat
; the timer trick, but often its important to know 
; just what scan line we're at.

	sta WSYNC;We do a WSYNC just before that so we don't turn on

	sta VBLANK;End the VBLANK period with the zero

;*********************** Scan line Loop
ScanLoop

	sta WSYNC;Wait for the previous line to finish

	lda player0buffer;buffer was set during last scanline

	sta GRP0;put it as graphics now

	cpy player0y; compare the player's y position

	bne SkipActivatePlayer0; if it isn't 0 then jump to SkipActivePlayer0

	lda #5; otherwise load our accumulatior with the number of lines to draw

	sta visibleplayer0line; and store it 

SkipActivatePlayer0

;set player buffer to all zeros for this line, and then see if 
;we need to load it with graphic data

	lda #0		

	sta player0buffer;set buffer, not GRP0

;if the VisiblePlayerLine is non zero,
;we're drawing it next line

	ldx visibleplayer0line;check the visible player line...

	beq FinishPlayer;skip the drawing if its zero...

	lda player0-1,X;otherwise, load the correct line from player0
	;section below... it's off by 1 though, since at zero
	;we stop drawing
	sta player0buffer;put that line as player graphic for the next line

	dec visibleplayer0line;and decrement the line count

FinishPlayer

; here the idea is that visiblemissile0line
; is zero if the line isn't being drawn now,
; otherwise it's however many lines we have to go

CheckActivateMissile

	cpy missile0y; is missile 0's y position the same as the current scanline?

	bne SkipActivateMissile; if it isn't then don't set missle 0's visible lines

	lda #8; otherwise set the missiles visible lines to 8

	sta visiblemissile0line; and store it in the visiblemissileline

SkipActivateMissile

;turn missile off then see if it's turned on

	lda #0

	sta ENAM0; disable the missile

;if the visiblemissile0line is non zero,
;we're drawing it

	lda visiblemissile0line; if the visiblemissle line is zero

	beq FinishMissile; don't draw the missile

	lda #2; otherwise set the accumulator to 2		

	sta ENAM0; and draw the missile

	dec visiblemissile0line; and decrement the visiblemissileline by 1

	inc missile0y; increment missle 0's y position by 1

FinishMissile

	dey;subtract one off the line counter thingy

	bne ScanLoop;and repeat if we're not finished with all the scanlines.

	lda #2;#2 for the VBLANK...

	sta WSYNC;Finish this final scanline.

	sta VBLANK; Make TIA output invisible for the overscan, 
; (and keep it that way for the vsync and vblank)

;***************************** OVERSCAN CALCULATIONS
;I'm just gonna count off the 30 lines of the overscan.
;You could do more program code if you wanted to.

	ldx #30;store 30

OverScanWait

	sta WSYNC

	dex

	bne OverScanWait

	jmp  GameLoop;Continue this loop forver! Back to the code for the vsync etc

PositionSprite

sta HMCLR

sec

sta WSYNC
	
PositionSpriteLoop

sbc	#15

bcs	PositionSpriteLoop

eor	#7

asl

asl

asl

asl			  

sta.wx HMP0,X	

sta	RESP0,X  

sta	WSYNC	  

sta	HMOVE	

rts

; here's the actual player0 graphic

player0
		.byte #%00011000
		.byte #%00111100
		.byte #%11111111
		.byte #%00111100
		.byte #%00011000

update_low_score_digits

	sed; set decimal mode

	clc; clear carry status

	adc score; add accumulator to score's low digits w/carry.

	sta score; store the updated low digits.

;NOTE: Here's where a triple-NOP comes into play.  We need
;a seperate entrypoint to this subroutine for cases where the
;low digits are ignored (like adding 100, for example).  But
;carry status and BCD mode need to have been setup.  So,
;place the triple-NOP opcode here to skip over them...
;with A reset at zero so that only carry affects the score:

	lda #0; reset the accumulator...

	.byte $0C; ...and skip over the next 2 bytes

update_middle_score_digits

	sed; set decimal mode

	clc; clear carry status

	adc score+1; add accumulator to score's middle digits w/carry.

	sta score+1; store the updated middle digits

;Here we do the same thing (in case the game needs to add 10,000...
;or 100,000 increments to a score (ignoring all the lower ones)
;Again, A is reset at zero so that only carry affects the score:

	lda #0; reset the accumulator...

	.byte $0C; ...and skip over the next 2 bytes

update_high_score_digits

	sed; set decimal mode

	clc; clear carry status

	adc score+1; add accumulator to score's high digits w/carry.

	sta score+2; store the last 2 digits

;With the score updated, clear BCD mode and exit via RTS:

	cld; clear decimal mode

	rts; and return to the program line that called this routine.

;*************************************************************************
; Interrupt Vectors

	ORG $FFFA

InterruptVectors

	.word Start	; NMI

	.word Start	; RESET

	.word Start	; IRQ

	END

 

Sincerely,

 

Primordial Ooze

PrimordialOoze.bin

Edited by Primordial Ooze
Link to comment
Share on other sites

Primordial Ooze, you can also save some bytes like this:

 

StartNewGame
   lda #105
   sta player0x; player0's initial x position
   lda #40
   sta player0y; player0's initial y position
   lda #3
   sta lives; start the player with 3 lives
   lda #0
   sta missile0x; missile 0's initial x position
   sta missile0y; missile 0's initial y position
   sta score; set high bit of score inital value to 0
   sta score+1; set nibble bit of score inital value to 0
   sta score+2; low bit of score inital value to 0

 

Because you don't need to reload the accumulator with #0 every time. You can also move all the registers you need to zero out beside each other and put it in a loop:

 

 

	ldx	#5			  ; number of times through loop
lda	#0			  ; value to be stored
.loopClearRam
sta	missile0x,X	; all the regsiters have been lined up in ram before hand
dex				   ; decrease X
bne	.loopClearRam  ; this loop is taken until X = 0

 

I presume later on StartNewGame will be used when the reset switch is hit. As it is right now though registers have already been cleared in the intial clear ram and all TIA registers. There are certain ram locations that are more beneficial to link side by side then others, particularly the ones that hold your position values.

Link to comment
Share on other sites

Primordial Ooze, you can also save some bytes like this:

 

StartNewGame
   lda #105
   sta player0x; player0's initial x position
   lda #40
   sta player0y; player0's initial y position
   lda #3
   sta lives; start the player with 3 lives
   lda #0
   sta missile0x; missile 0's initial x position
   sta missile0y; missile 0's initial y position
   sta score; set high bit of score inital value to 0
   sta score+1; set nibble bit of score inital value to 0
   sta score+2; low bit of score inital value to 0

 

Because you don't need to reload the accumulator with #0 every time. You can also move all the registers you need to zero out beside each other and put it in a loop:

 

 

	ldx	#5			 ; number of times through loop
lda	#0			 ; value to be stored
.loopClearRam
sta	missile0x,X; all the regsiters have been lined up in ram before hand
dex				  ; decrease X
bne	.loopClearRam ; this loop is taken until X = 0

 

I presume later on StartNewGame will be used when the reset switch is hit. As it is right now though registers have already been cleared in the intial clear ram and all TIA registers. There are certain ram locations that are more beneficial to link side by side then others, particularly the ones that hold your position values.

Thanks, i will do that. Any solutions to my problem?

 

Sincerely,

 

Primordial Ooze

Link to comment
Share on other sites

I believe you also need a flag to test if a missile is already onscreen.

 

Otherwise, your code might keep initiating the missile fire because the button is held.

 

You might try using the Missile X-Pos. Just have it set at 0 to signify that no missile is onscreen.

 

Then all you need to do is test the X-Pos before your button checking code.

If X-Pos is non-zero, then skip the button check.

 

Of course, you'll need to set Missile X-Pos back to 0 once it's no longer needed.

Link to comment
Share on other sites

I believe you also need a flag to test if a missile is already onscreen.

 

Otherwise, your code might keep initiating the missile fire because the button is held.

 

You might try using the Missile X-Pos. Just have it set at 0 to signify that no missile is onscreen.

 

Then all you need to do is test the X-Pos before your button checking code.

If X-Pos is non-zero, then skip the button check.

 

Of course, you'll need to set Missile X-Pos back to 0 once it's no longer needed.

Actually i can do it using missile0y, as as soon as missile0y hits 0 it stops moving and being drawn. The other problem i am having is the missile "caving in" and merging with the player sprite when you move the player towards the left. Any ideas on why this is happening?

 

Sincerely,

 

Primordial Ooze

Link to comment
Share on other sites

You could explicitly align all the players and missiles during vertical blank. Here is some excellent assembly code that I found on these boards a while ago. I don't know the original authors name.

 

This subroutine will position any of the graphical objects on the screen in the specified column. You just need to assign the registers and JSR.

 

Just note that the HMOVE is not cleared after the call. You need to clear it after horizontal blank is over.

 

;---------------------------------------------------------------
; Subroutine: PosSprite
;
; In	   : a = position.
;			x = sprite (0 = player 0, 1 = player 1, 
;						2 = missile 0, 3 = missile 1, 4 = ball)
;
; Out	  : None
;
; Destroyed: A
;---------------------------------------------------------------

PosSprite
STA   HMCLR
SEC
STA   WSYNC	;					  begin line 1

PosSpriteLoop
SBC	#15
BCS	PosSpriteLoop ;+4/5	4/ 9.../54

EOR	#7			;+2	  6/11.../56
ASL
ASL
ASL
ASL				  ;+8	 14/19.../64

STA.wx HMP0,X		;+5	 19/24.../69
STA	RESP0,X	;+4	 23/28/33/38/43/48/53/58/63/68/73
STA	WSYNC		 ;+3	 0			  begin line 2
STA	HMOVE		 ;+3
RTS				  ;+6	 9

Link to comment
Share on other sites

Your problem is that in your kernel, you enable the missile too late in the line, so on the left side of the screen, the missile wont move vertically. Here is a fixed source and binary.

Thanks for fixing my code. What i don't understand is what you mean by drawing it "late on the scanline". I'm using modified code from the joystick example in Atari 2600 Programming 101 and couldn't figure out what i did wrong. Could you please explain it?

 

Sincerely,

 

Primordial Ooze

Edited by Primordial Ooze
Link to comment
Share on other sites

Your problem is that in your kernel, you enable the missile too late in the line, so on the left side of the screen, the missile wont move vertically. Here is a fixed source and binary.

Thanks for fixing my code. What i don't understand is what you mean by drawing it "late on the scanline". I'm using modified code from the joystick example in Atari 2600 Programming 101 and couldn't figure out what i did wrong. Could you please explain it?

 

Sincerely,

 

Primordial Ooze

 

In a 2600 kernel, you are storing to the graphics registers just cycles before they are drawn on the screen. Your kernel was attempting to enable the Missile sprite on a pixel that had already been drawn by the time your kernel enabled it. Hope that makes more sense.

 

-Rick

Link to comment
Share on other sites

Your problem is that in your kernel, you enable the missile too late in the line, so on the left side of the screen, the missile wont move vertically. Here is a fixed source and binary.

Thanks for fixing my code. What i don't understand is what you mean by drawing it "late on the scanline". I'm using modified code from the joystick example in Atari 2600 Programming 101 and couldn't figure out what i did wrong. Could you please explain it?

 

Sincerely,

 

Primordial Ooze

 

In a 2600 kernel, you are storing to the graphics registers just cycles before they are drawn on the screen. Your kernel was attempting to enable the Missile sprite on a pixel that had already been drawn by the time your kernel enabled it. Hope that makes more sense.

 

-Rick

Now that i looked at my code and your code side by side, i see what you mean. In my game missile0 always had a higher scanline then player0, however in my game code it always drew player0 first and then the missile which the scanline was already passed through. So to fix my code you just moved my missile code to the beginning of the scanline loop so missile0 is drawn first and then then player0 like it should. Thanks for the explaination, it makes alot of sense! :D

 

Sincerely,

 

Primordial Ooze

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...