ZX Spectrum Assembly, Space Battle – 0x07 Collisions and level change
In this chapter of ZX Spectrum Assembly, we will include the collisions of the shot with the enemies, the enemies with the ship and the level changes.
We create the folder Step07 and copy from Step06: make, or make.bat if you are on Windows, loader.tap, const.asm, ctrl.asm, game.asm, graph.asm, int.asm, main.asm, print.asm and var.asm.
Translation by Felipe Monge Corbalán
Table of contents
- Enemy collisions with the shot
- Level change
- Collisions between enemies and the ship
- ZX Spectrum Assembly, Space Battle
- Useful links
Enemy collisions with the shot
First we implement the collisions between the enemies and the shot. In the first byte of each enemy’s configuration, bit seven, we are told whether it is active or not, so we can decide whether to paint it or not.
The routine we are going to implement checks if an enemy is in the same coordinates as the shot, and if so, deactivates it.
We implement this routine at the beginning of the file game.asm.
CheckCrashFire:
ld a, (flags)
and $02
ret z
We load the value of the flags into A, LD A, (flags), leave bit one to check if the shot is active, AND $02, and exit if it is not, RET Z.
ld de, (firePos)
ld hl, enemiesConfig
ld b, enemiesConfigEnd - enemiesConfigIni
sra b
We load in DE the coordinates of the shot, LD DE, (firePos), in HL the configuration of the enemies, LD HL, enemiesConfig, in B the total number of bytes of configuration, LD B, enemiesConfigEnd – enemiesConfigIni, we divide it by two, SRA B, and in this way we obtain the number of enemies; the configuration of each one occupies two bytes.
SRA shifts all the bits to the right, sets bit zero in the carry and holds bit seven to preserve the sign. SRA does an integer division by two, and since the number of enemies we have is even, it works for us.
checkCrashFire_loop:
ld a, (hl)
inc hl
bit $07, a
jr z, checkCrashFire_endLoop
We load the first byte of the configuration into A, LD A, (HL), point HL to the second byte, INC HL, check if the enemy is active, BIT $07, A, and jump, JR Z, checkCrashFire_endLoop, if not.
and $1f
cp d
jr nz, checkCrashFire_endLoop
If the enemy is active, we keep the Y-coordinate, AND $1F, compare it with the shot, CP D, and jump if they are not the same, JR NZ, checkCrashFire_endLoop.
ld a, (hl)
and $1f
cp e
jr nz, checkCrashFire_endLoop
We load in A the second byte of the enemy configuration, LD A, (HL), leave the X coordinate, AND $1F, compare it with the shot, CP E, and jump, JR NZ, checkCrashFire_endLoop, if they are not the same.
dec hl
res 07, (hl)
ld b, d
ld c, e
call DeleteChar
ret
If shot and enemy collide, we point HL to the first byte of the enemy configuration, DEC HL, disable the enemy, RES $07, (HL), load the Y-coordinate of the shot into B, LD B, D, the X-coordinate into C, LD C, E, delete what is in the coordinates, CALL DeleteChar, and exit the routine, RET.
checkCrashFire_endLoop:
inc hl
djnz checkCrashFire_loop
ret
If fire and enemy do not collide, we point HL to the first byte of the next enemy configuration, INC HL, and repeat the loop until B is zero, DJNZ checkCrashFire_loop. At the end of the loop we exit the routine, RET.
The final aspect of the routine is as follows:
; -------------------------------------------------------------------
; Evaluates the collisions of the shot with enemies.
;
; Alters the value of the AF, BC, DE and HL registers.
; -------------------------------------------------------------------
CheckCrashFire:
ld a, (flags) ; A = flags
and $02 ; Active fire?
ret z ; Not active, exits
ld de, (firePos) ; DE = firing position
ld hl, enemiesConfig ; HL = def 1st enemy
ld b, enemiesConfigEnd-enemiesConfigIni ; B = number of config bytes
sra b ; B = B / 2, number of enemies
checkCrashFire_loop:
ld a, (hl) ; A coord Y enemy
inc hl ; HL = enemy coord X
bit $07, a ; Active enemy?
jr z, checkCrashFire_endLoop ; Not active, skips
and $1f ; A = coord Y enemy
cp d ; Compare coord Y disp
jr nz, checkCrashFire_endLoop ; Distinct, jumps
ld a, (hl) ; A = enemy X coord
and $1f ; A = coord X
cp e ; Compare coord X disp
jr nz, checkCrashFire_endLoop ; Distinct, jumps
dec hl ; HL = coord Y enemy
res $07, (hl) ; Deactivates enemy
ld b, d ; B = coord Y shot
ld c, e ; C = coord X
call DeleteChar ; Delete trigger/enemy
ret ; Exits
checkCrashFire_endLoop:
inc hl ; HL = coord Y next
djnz checkCrashFire_loop ; Loop as long as B > 0
ret
We test if the collisions work. We open main.asm, go to the Main_loop tag, and under CALL MoveFire we preserve the value of DE (it has the controls’ keystrokes), PUSH DE. We include the call to the previous routine, CALL CheckCrashFire, and we restore the value of DE, POP DE, which looks like this:
Main_loop:
call CheckCtrl
call MoveFire
push de
call CheckCrashFire
pop de
call MoveShip
call MoveEnemies
jr Main_loop
We compile, load into the emulator and test. We see that we have two problems, one of which is inherited:
- If we don’t move the ship, it will be erased and not painted again.
- Once there are no more ships, all we can do is reload the game.
The first problem will not be addressed. If the ship is destroyed after colliding with an enemy, we will include the explosion later.
Level change
For the level change, the first thing we have to control is the number of active enemies, when we reach zero we have to change the level. The second thing is the number of levels there are, thirty in total. For now, when we reach level thirty-one, we go back to level one. Later the game will end.
We open var.asm and add a variable for the number of active enemies and another for the current level, at the beginning, after the game information title.
; -------------------------------------------------------------------
; Information about the game
; -------------------------------------------------------------------
enemiesCounter:
db $14
levelCounter:
db $01
Before implementing the level-changing routine, we made some changes to use levelCounter. We open the graph.asm file and locate the LoadUdgsEnemies routine. This routine receives the level in A, which is no longer necessary as it takes this value from levelCounter. We add the following line to the top of the routine:
ld a, (levelCounter)
In A, we load the current level, LD A, (levelCounter).
In the comments of the routine, we delete the line referring to the entry in A of the level, leaving the following:
; -------------------------------------------------------------------
; Load enemy-related graphics
;
; Alters the value of the AF, BC, DE and HL registers.
; -------------------------------------------------------------------
LoadUdgsEnemies:
ld a, (levelCounter) ; A = level
dec a ; A = A - 1, do not add one level of more
ld h, $00 ; H = 0
ld l, a ; L = A, HL = level - 1
add hl, hl ; Multiply by 2
add hl, hl ; by 4
add hl, hl ; by 8
add hl, hl ; by 16
add hl, hl ; by 32
ld de, udgsEnemiesLevel1 ; DE = enemy address 1
add hl, de ; HL = HL + DE
ld de, udgsExtension ; DE = extension address
ld bc, $20 ; BC = bytes to copy, 32
ldir ; Copies enemy bytes in extension
ret
In game.asm we look for the tag checkCrahsFire_endLoop, above it is a RET and above this RET we add the following lines:
ld hl, enemiesCounter ; HL = enemiesCounter
dec (hl) ; Subtract one enemy
In main.asm, three lines above Main_loop, just before CALL LoadUdgsEnemies, we delete the line LD A, $01; we get the level from levelCounter.
Compile, load into the emulator and check that everything still works.
In game.asm we implement the level change: we load the graphics of the enemies of the next level, reset their configuration and update the counters added earlier.
ChangeLevel:
ld a, (levelCounter)
inc a
cp $1f
jr c, changeLevel_end
ld a, $01
We load the current level into A, LD A, (levelCounter), move to the next level by incrementing A, INC A, and check if we have reached level thirty-one, CP $1F. If we have not, we jump to the last part of the routine, JR C, changeLevel_end. If we have reached level thirty-one, remember we have thirty levels, we don’t jump and set A to $01.
changeLevel_end:
ld (levelCounter), a
call LoadUdgsEnemies
ld a, $14
ld (enemiesCounter), a
ld hl, enemiesConfigIni
ld de, enemiesConfig
ld bc, enemiesConfigEnd-enemiesConfigIni
ldir
ret
We load the next level into memory, LD (levelCounter), A, the enemy graphics, CALL LoadUdgsEnemies, the total number of enemies in A, LD A, $14, and update, LD (enemiesCounter), A.
We restart the configuration: we point HL to the initial configuration, LD HL, enemiesConfigIni, DE to the current configuration, LD DE, enemiesConfig, load the bytes occupied by the configuration into BC, LD BC, enemiesConfigEnd – enemiesConfigIni, pass the initial to the current, LDIR, and exit, RET.
The last aspect of the routine is as follows:
; -------------------------------------------------------------------
; Change level.
;
; Alters the value of the AF, BC, DE and HL registers.
; -------------------------------------------------------------------
ChangeLevel:
ld a, (levelCounter) ; A = current level
inc a ; A = next level
cp $1f ; Level 31?
jr c, changeLevel_end ; Is not 31, skip
ld a, $01 ; If 31, level = 1
changeLevel_end:
ld (levelCounter), a ; Update level in memory
call LoadUdgsEnemies ; Load enemy graphics
ld a, $14 ; A = total number of enemies
ld (enemiesCounter), a ; Loads it into memory
ld hl, enemiesConfigIni ; HL = initial configuration
ld de, enemiesConfig ; DE = current configuration
ld bc, enemiesConfigEnd - enemiesConfigIni ; BC = long config
ldir ; Initial configuration = current
ret
Finally, we use the implementation. We go to main.asm, to the MainLoop routine, find the fifth line, POP DE, and add the following below it:
ld a, (enemiesCounter)
or a
jr z, Main_restart
We load into A the number of enemies still active, LD A, (enemiesCounter), check if we have reached zero, OR A, and jump if so, JR Z, Main_restart.
Go to the end of the file and add the following before the first include:
Main_restart:
call ChangeLevel
jr Main_loop
We move to the next level, CALL ChangeLevel, and return to the start of the loop, JR Main_loop.
As main.asm grows, let’s see how it should look now:
org $5dad
; -------------------------------------------------------------------
; Indicators
;
; Bit 0 -> ship must be moved 0 = No, 1 = Yes
; Bit 1 -> Trigger is active 0 = No, 1 = Yes
; Bit 2 -> Enemies must be moved 0 = No, 1 = Yes
; -------------------------------------------------------------------
flags:
db $00
Main:
ld a, $02
call OPENCHAN
ld hl, udgsCommon
ld (UDG), hl
ld hl, ATTR_P
ld (hl), $07
call CLS
xor a
out ($fe), a
ld a, (BORDCR)
and $c7
or $07
ld (BORDCR), a
call PrintFrame
call PrintInfoGame
call PrintShip
di
ld a, $28
ld i, a
im 2
ei
call LoadUdgsEnemies
call PrintEnemies
Main_loop:
call CheckCtrl
call MoveFire
push de
call CheckCrashFire
pop de
ld a, (enemiesCounter)
or a
jr z, Main_restart
call MoveShip
call MoveEnemies
jr Main_loop
Main_restart:
call ChangeLevel
jr Main_loop
include "const.asm"
include "var.asm"
include "graph.asm"
include "print.asm"
include "ctrl.asm"
include "game.asm"
end Main
We compile, load into the emulator and, if all goes well, see how the enemies change when we have killed them all.
Collisions between enemies and the ship
In this first approach, we just paint an explosion when an enemy collides with the ship. Later we will subtract a life. First we implement the routine that draws the explosion. Let’s go to the print.asm file.
PrintExplosion:
ld a, $02
call Ink
ld bc, (shipPos)
ld d, $04
ld e, $92
In A we load two (two = red colour), LD A, $02, and change the colour of the ink, CALL Ink. We load into BC the position of the ship, LD BC, (shipPos), into D the number of UDGs the explosion has, LD D, $04, and into E the first UDG of the explosion, LD E, $92.
printExplosion_loop:
call At
ld a, e
rst $10
halt
halt
halt
halt
inc e
dec d
jr nz, printExplosion_loop
jp PrintShip
We position the cursor on the ship’s coordinates, CALL At, load the UDG in A, LD A, E, and paint it, RST $10. We wait four interrupts, HALT, HALT, HALT, HALT, point E to the next UDG, INC E, decrement D, DEC D, and continue in the loop, JR NZ, printExplosion_loop, until D reaches zero.
We paint the ship and walk away, JP PrintShip. We use PrintShip’s RET to exit. We could call PrintShip and exit, but with JP we save one byte and seventeen clock cycles.
The final aspect of the routine is as follows:
; -------------------------------------------------------------------
; Paints the explosion of the ship
;
; Alters the values of the AF, BC and DE registers.
; -------------------------------------------------------------------
PrintExplosion:
ld a, $02 ; A = 2 (red)
call Ink ; Ink = red
ld bc, (shipPos) ; BC = ship position
ld d, $04 ; D = UDG explosion number
ld e, $92 ; E = 1st UDG explosion
printExplosion_loop:
call At ; Position cursor
ld a, e ; A = UDG
rst $10 ; Paints it
halt
halt
halt
halt ; Wait for 4 interruptions
inc e ; E = next UDG
dec d ; D = D-1
jr nz, printExplosion_loop ; Loop until D = 0
jp PrintShip ; Paints ship and goes out that way
Now, in game.asm, we are going to implement the collisions between the enemies and the ship, which, as you will see, is very similar to the collision routine of the enemies with the shot.
CheckCrashShip:
ld de, (shipPos)
ld hl, enemiesConfig
ld b, enemiesConfigEnd-enemiesConfigIni
sra b
We load in HL the position of the ship, LD DE, (shipPos), HL we point it to the configuration of the enemies, LD HL, enemiesConfig, we load in B the total number of bytes of the configuration, LD B, enemiesConfigEnd – enemiesConfigIni, and we divide it by two to get the number of enemies, SRA B.
checkCrashShip_loop:
ld a, (hl)
inc hl
bit $07, a
jr z, checkCrashShip_endLoop
We load the first byte of the enemy configuration into A, LD A, (HL), point HL to the second byte, INC HL, check if the enemy is active, BIT $07, A, and skip if not, JR Z, checkCrashShip_endLoop.
and $1f
cp d
jr nz, checkCrashShip_endLoop
We keep the Y-coordinate of the enemy at A, AND $1F, compare it with the Y-coordinate of the ship, CP D, and jump if they are not the same, JR NZ, checkCrashShip_endLoop.
ld a, (hl)
and $1f
cp e
jr nz, checkCrashShip_endLoop
We load the second byte of the enemy configuration in A, LD A, (HL), keep the X coordinate, AND $1F, and see if it matches that of the ship, CP E. We skip, JR NZ, checkCrashShip_endLoop, if they are not the same.
dec hl
res 07, (hl)
ld hl, enemiesCounter
dec (hl)
jp PrintExplosion
If we go through here, there has been a collision. We point HL to the first byte of the enemy configuration, DEC HL, and disable the enemy, RES $07,(HL). We point HL at the counter, LD HL, enemiesCounter, and subtract one, DEC (HL). Finally, we jump to paint the explosion and exit, JP PrintExplosion, using the same technique we saw in PrintExplosion.
checkCrashShip_endLoop:
inc hl
djnz checkCrashShip_loop
ret
If there has been no collision, we point HL to the first byte of the next enemy’s configuration, INC HL, and continue in the loop until B is zero and we have traversed all the enemies, DJNZ checkCrashShip_loop. Finally, we exit, RET.
The final aspect of the routine is as follows:
; -------------------------------------------------------------------
; Evaluates enemy collisions with the ship.
;
; Alters the value of the AF, BC, DE and HL registers.
; -------------------------------------------------------------------
CheckCrashShip:
ld de, (shipPos) ; DE = ship position
ld hl, enemiesConfig ; HL = enemiesConfig
ld b, enemiesConfigEnd-enemiesConfigIni ; ; B = bytes config
sra b ; B = B/2 = number of enemies
checkCrashShip_loop:
ld a, (hl) ; A = enemy Y-coordinate
inc hl ; HL = coord X
bit $07, a ; Active enemy?
jr z, checkCrashShip_endLoop ; Not active, skips
and $1f ; A = coord Y enemy
cp d ; Compare with ship
jr nz, checkCrashShip_endLoop ; Distinct, skip
ld a, (hl) ; A = enemy X coord
and $1f ; A = coord X
cp e ; Compare with ship
jr nz, checkCrashShip_endLoop ; Distinct, skip
dec hl ; HL = coord Y enemy
res $07, (hl) ; Deactivates enemy
ld hl, enemiesCounter ; HL = enemiesCounter
dec (hl) ; Subtract one enemy
jp PrintExplosion ; Paint explosion and it comes out
checkCrashShip_endLoop:
inc hl ; HL = coord Y next enemy
djnz checkCrashShip_loop ; Loop until B = 0
ret
It is time to test the collisions between the ship and the enemies. We open main.asm, locate Main_loop and see that the last line is JR Main_loop. Above this line we will add the call to test the collisions between the ship and the enemies:
call CheckCrashShip
We compile, load in the emulator and see the results.
ZX Spectrum Assembly, Space Battle
We have implemented collisions between shot and enemy, and between enemy and ship. Also, the level changes when we destroy all the enemies.
In the next chapter of ZX Spectrum Assembly, we will implement the scoreboard and a transition between levels.
Download the source code from here.
Useful links
ZX Spectrum Assembly, Space Battle by Juan Antonio Rubio García.
Translation by Felipe Monge Corbalán.
This work is licensed to Creative Commons Attribution-NonCommercial-ShareAlike 4.0 International (CC BY-NC-SA 4.0).
Any comments are always welcome.