ZX Spectrum Assembly, Space Battle – 0x0B Enemy behaviour
In this chapter of ZX Spectrum Assembly, we will focus on the behaviour of the enemies.
We create Step11 and copy from Step10 loader.tap, const.asm, ctrl.asm, game.asm, graph.asm, int.asm, main.asm, make or make.bat, print.asm and var.asm.
Translation by Felipe Monge Corbalán
Tabla de contenidos
- Changes of direction
- Colour change
- Enemy shots
- Difficulty setting
- ZX Spectrum Assembly, Space Battle
- Useful links
Changes of direction
To make enemy movement a little less predictable, the direction of the enemies will change every four seconds.
The first thing to do is to open main.asm, locate the flags tag and add a comment for bit three.
; -------------------------------------------------------------------
; Indicators
;
; Bit 0 -> ship must be moved 0 = No, 1 = Yes
; Bit 1 -> shot is active 0 = No, 1 = Yes
; Bit 2 -> enemies must be moved 0 = No, 1 = Yes
; Bit 3 -> change address enemies 0 = No, 1 = Yes
; -------------------------------------------------------------------
flags:
db $00
Every four seconds we will activate bit three and the enemies will change direction.
So that the enemies do not always change direction, we will use an extra tag. Open var.asm, go to the extraCounter tag and add the following lines:
; -------------------------------------------------------------------
; Auxiliary values
; -------------------------------------------------------------------
swEnemies:
db $00
enemiesColor:
db $06
The tag we are going to use is swEnemies. As you can see, I’ve added another tag that we’re going to use to add a little colour effect to the enemies.
Now we are going to implement the routine that will change the direction of the enemies. We will open game.asm and implement the routine that changes the direction of the enemies at the beginning.
ChangeEnemies:
ld hl, flags
bit $03, (hl)
ret z
res 03, (hl)
ld b, $14
ld hl, enemiesConfig
ld a, (swEnemies)
ld c, a
We load into HL the address of the flags memory, LD HL, flags, check if bit three is set (address change), BIT $03, (HL), and exit if it is not, RET Z.
Deactivate the bit if it is set, RES $03, (HL), load into B the total number of enemies, LD B, $14, load into HL the address of the enemy configuration, LD HL, enemiesConfig, load into A the value of the auxiliary tag indicating the change of enemy address, LD A, (swEnemies), and preserve the value by loading it into C, LD C, A.
changeEnemies_loop:
bit $07, (hl)
jr z, changeEnemies_endLoop
inc hl
ld a, (hl)
and $3f
or c
ld (hl), a
dec hl
ld a, c
add a, $40
ld c, a
We check if the enemy is active, BIT $07, (HL), and if not, we jump.
The address of the enemy is in bits six and seven of the second byte of the configuration, so we point HL to this second byte, INC HL, load it into A, LD A, (HL), discard the current address, AND $3F, add the new one, OR C, and update in memory, LD (HL), A.
Point HL back to the first byte of the configuration, DEC HL, load the new address into A, LD A, C, add one ($40 = 0100 0000), ADD A, $40, and load the value into C, LD C, A.
changeEnemies_endLoop:
inc hl
inc hl
djnz changeEnemies_loop
We point HL to the first byte of the next enemy, INC HL, INC HL, and repeat until B is zero and we have gone through all the enemies, DJNZ changeEnemies_loop.
changeEnemies_end:
ld a, c
ld (swEnemies), a
ret
We load the new address into A, LD A, C, load the value into memory for the next time the address needs to be changed, LD (swEnemies), A, and exit, RET.
The last aspect of the routine is as follows:
; -------------------------------------------------------------------
; Changes the direction of enemies.
;
; Alters the value of the AF, BC and HL registers.
; -------------------------------------------------------------------
ChangeEnemies:
ld hl, flags ; HL = address flags
bit $03, (hl) ; Bit 3 active?
ret z ; Not active, exits
res $03, (hl) ; Disables bit 3
ld b, $14 ; B = number of enemies (20)
ld hl, enemiesConfig ; HL = enemiesConfig
ld a, (swEnemies) ; A = aux change direction
ld c, a ; C = A (new address)
changeEnemies_loop:
bit $07, (hl) ; Active enemy?
jr z, changeEnemies_endLoop ; Not active, skips
inc hl ; HL = 2nd byte config
ld a, (hl) ; A = 2nd byte
and $3f ; Discard the address
or c ; A = new address
ld (hl), a ; Update in memory
dec hl ; HL = 1st byte config
ld a, c ; A = C (new address)
add a, $40 ; Add one dir ($40=01000000)
ld c, a ; C = A (new address)
changeEnemies_endLoop:
inc hl ; HL 1st byte next config
inc hl ; enemy
djnz changeEnemies_loop ; Until B = 0 (20 enemies)
changeEnemies_end:
ld a, c ; A = C (new address)
ld (swEnemies), a ; Update in-memory
ret
This new routine needs to be called from the main loop of the program. Go back to main.asm, find Main_loop, find the CALL MoveShip line, and add the following just below it:
call ChangeEnemies
Try to compile, load in the emulator and you will see that everything remains the same, we have not broken anything and the address change does not occur because we do not activate bit three of the flags.
We open int.asm to implement the activation of this bit every four seconds (on PAL systems), thus using interrupts.
The first thing we will do is add a constant to the top of the file, just below ORG $7E5C:
T1: EQU $c8
We assign $C8 (two hundred) to T1, which is the result of multiplying fifty interrupts per second by four seconds.
At the end of the file we add a tag to keep track of the interrupts until they reach two hundred and four seconds.
countT1: db $00
Now we modify the interrupt routine. We locate the Isr_end tag, and just above it we implement the part that controls the four seconds we talked about.
Isr_T1:
ld a, (countT1)
inc a
ld (countT1), a
sub T1
jr nz, Isr_end
ld (countT1), a
set 03, (hl)
We load the counter in A, LD A, (countT1), add one, INC A, and update the value of the counter, LD (countT1), A.
We subtract the interrupts that must be reached to activate the change of direction flag, SUB T1, and skip them if they are not reached, JR NZ, Isr_end.
When four seconds have been reached, the result of the above subtraction is zero and we update the counter, LD (countT1), A. Finally, we set the address change bit, SET $03, (HL).
Three lines above Isr_T1 we find the JR NZ line, Isr_end, which we change to this:
jr nz, Isr_T1
Now we compile, load the emulator and check that the enemies change direction every four seconds. In the same way, we can see that going to the right and shooting doesn’t work so well, maybe in the first level, but not in the following ones.
We are forcing the player to move, but the enemy’s speed does not allow us to see where he is going, so we should slow down the enemy’s speed. We go back to int.asm and find the part where the bit for moving enemies is activated:
ld a, (countEnemy)
inc a
ld (countEnemy), a
sub $02
jr nz, Isr_T1
ld (countEnemy), a
set 02, (hl)
Change SUB $02 to SUB $03.
Compile, load in the emulator and see if it runs better. Adjust the speed to your liking; we still need to work on the behaviour of the enemies.
Colour change
As I mentioned earlier in this chapter, we are going to add a colour effect to the movement of the enemies, for which we have added the enemiesColor tag to var.asm.
The effect is to change the colour of the enemies from one (blue) to seven (white) every time they move.
Let’s go to print.asm and locate PrintEnemies, and just below that we’ll add the implementation of the colour effect.
The first thing we need to do is change the first line of the rutia, LD A, $06.
ld a, (enemiesColor) ; A = ink
The colour in which the enemies are painted is taken from this new label.
The first time we paint the enemies in each level, we paint them yellow. Open game.asm, locate ChangeLevel and add these two lines at the top:
ld a, $06 ; A = yellow
ld (enemiesColor), a ; Update colour in memory
When we compile and load in the emulator, we see that the enemies are still painted in yellow.
We follow game.asm and find the MoveEnemies tag, which looks like this:
MoveEnemies:
ld hl, flags ; HL = flags memory address
bit $02, (hl) ; Bit 2 active?
ret z ; Not active, exits
res $02, (hl) ; Disables bit 2 of flags
ld d, $14 ; D = total number of enemies (20)
ld hl, enemiesConfig ; HL = enemies config address
moveEnemies_loop:
The colour change is implemented immediately after the RES $02, (HL) line.
ld a, (enemiesColor)
inc a
cp $08
jr c, moveEnemies_cont
ld a, $01
moveEnemies_cont:
ld (enemiesColor), a
We load the colour in A, LD A, (enemiesColor), add one, INC A, check if it has reached eight, CP $08, and jump if it hasn’t, JR C, moveEnemies_cont. If we didn’t jump, we reached eight and set the colour to blue, LD A, $01. Finally, we update the colour in memory, LD (enemiesColor), A.
The start of the routine looks like this:
MoveEnemies:
ld hl, flags ; HL = flags memory address
bit $02, (hl) ; Bit 2 active?
ret z ; Not active, exits
res $02, (hl) ; Disables bit 2 of flags
ld a, (enemiesColor) ; A = enemiesColor
inc a ; It increases it
cp $08 ; ¿A = 8?
jr c, moveEnemies_cont ; Distinct, jumps
ld a, $01 ; A = colour blue
moveEnemies_cont:
ld (enemiesColor), a ; Update colour in memory
ld d, $14 ; D = total number of enemies (20)
ld hl, enemiesConfig ; HL = dir config enemies
moveEnemies_loop:
Compile and load into the emulator. Now we can see how the enemies change colour.
Enemy shots
We’ve changed the behaviour of the enemies, firstly so that we don’t just get through the thirty levels by staying in one part of the screen, and secondly to make the game more eye-catching.
The time has come for the most important change, we are going to equip our enemies with shooting.
Shooting enemies will be activated when they are above us, and there will be a maximum of five active shots at any one time.
The first step is to declare the constants we need. Open const.asm and look for WHITE_GRAPH, which is an EQU directive with a value of $9E, code that corresponds to the graphic defined for the blank, which is unnecessary since the blank character is defined in the ZX Spectrum, it is the character $20 (32). We leave the line as follows:
WHITE_GRAPH: EQU $20
Now locate ENEMY_TOP_R and just below it we will add constants for the total number of enemies, the character code for enemy shot and the number of shots that can be active at the same time.
ENEMIES: EQU $14
ENEMY_GRA_F: EQU $9e
FIRES: EQU $05
We see that the character code $9E becomes the enemy shot.
Open var.asm, find udgsCommon and go to the last line:
db $00, $00, $00, $00, $00, $00, $00, $00 ; $9e White
We change this line and leave it as follows:
db $00, $3c, $2c, $2c, $2c, $2c, $18, $00 ; $9e Enemy shot
If you have done the exercises in Step 1: Definition of graphics, you should be able to draw the representation of the enemy shot on paper or on the provided templates, you just need to do the conversion from hexadecimal to binary.
Just above udgsCommon we will add tags to configure the shots and to keep track of the number of active shots.
; -------------------------------------------------------------------
; Enemy shots configuration
;
; 2 bytes per shot.
; -------------------------------------------------------------------
; Byte 1 | Byte 2
; -------------------------------------------------------------------
; Bit 0-4: Position Y | Bit 0-4: X position
; Bit 5: Free | Bit 5: Free
; Bit 6: Free | Bit 6: Free
; Bit 7: Active 1/0 | Bit 7: Free
; -------------------------------------------------------------------
enemiesFire:
ds FIRES * $02
enemiesFireCount:
db $00
With DEFS, we reserve as many bytes as the result of multiplying FIRES (maximum number of enemy shots simultaneously) by two (bytes per shot). As you can see, the configuration of the enemy shots has some similarity to the configuration of the enemies.
Open up game.asm and let’s start with the implementation necessary for enemies to shoot and make things difficult.
We will implement a routine to disable all enemy shots, which we will call every time we start a new level. We will place this routine just before the Sleep routine.
ResetEnemiesFire:
ld hl, enemiesFire
ld de, enemiesFire + $01
ld bc, FIRES * $02
ld (hl), $00
ldir
ret
We point HL to the first byte of the enemiesFire configuration, LD HL, enemiesFire, DE we point it to the next byte, LD DE, enemiesFire + $01, we load into BC the number of bytes to clear, LD BC, FIRES * $02, we clear the first one, LD (HL), $02, we clear the rest, LDIR, and exit, RET.
Actually, we are also clearing (resetting) the active firing counter, which is not a problem. However, if you want to avoid this, you can set LD BC, FIRES * $02 – $01.
The appearance of the routine, once annotated, is as follows:
; -------------------------------------------------------------------
; Initialises the enemy firing configuration
;
; Alters the value of the BC, DE and HL registers.
; -------------------------------------------------------------------
ResetEnemiesFire:
ld hl, enemiesFire ; HL = shot configuration
ld de, enemiesFire + $01 ; DE = next byte
ld bc, FIRES * $02 ; BC = bytes to be cleared
ld (hl), $00 ; Clean 1st byte
ldir ; Clean remainder
ret
The enemy firing configuration is a kind of list. We need a routine that updates this list, sees which shots are active, puts them at the beginning and updates the number of active shots in memory. We’ll implement this just before ResetEnemiesFire.
We are unlikely to have more than five enemy shots active at any one time, maybe even less. Based on that, we are going to do a routine that is not the most optimal, but it works.
The routine will go through the whole list for each item, so we will use two nested loops. Finally, we implement a third loop that updates the number of active shots.
RefreshEnemiesFire:
ld b, FIRES
xor a
refreshEnemiesFire_loopExt:
push bc
ld ix, enemiesFire
ld b, FIRES
We load the maximum number of shots into B as the outer loop counter, LD B, FIRES, and set A to zero, XOR A. We keep BC, PUSH BC, point IX to the part of the enemy firing configuration, LD IX, enemiesFire, and reload the maximum number of shots into B as the inner loop counter, LD B, FIRES.
refreshEnemiesFire_loopInt:
bit $07, (ix+$00)
jr nz, refreshEnemiesFire_loopIntCont
ld c, (ix+$02)
ld (ix+$00), c
ld c, (ix+$03)
ld (ix+$01), c
ld (ix+$02), a
We evaluate if the fire is active, BIT $07, (IX+$00), and if it is, we skip, JR NZ, refreshEnemiesFire_loopIntCont.
If it is not active, we load the first byte of the next shot into C, LD C, (IX+$02), and load it into the first byte of the shot pointed to by IX, LD (IX+$00), C. We load the second byte of the next shot into C, LD C, (IX+$03), and load it into the second byte of the shot pointed to by IX, LD (IX+$01), C.
Finally, we set the first byte of the second shot to zero, LD(IX+$02), A.
refreshEnemiesFire_loopIntCont:
inc ix
inc ix
djnz refreshEnemiesFire_loopInt
pop bc
djnz refreshEnemiesFire_loopExt
We point IX to the first byte of the next shot, INC IX, INC IX, and repeat the operations in a loop, DJNZ refreshEnemiesFire_loopInt, until B is zero.
We get BC (this is the outer loop counter), PUSH BC, and repeat the loop operations, DJNZ refreshEnemiesFire_loopExt, until the value of B reaches zero.
At this point we have the active shots at the top of the list, and all that remains is to count how many shots are active. We will count the active shots in A, remembering that we already set it to zero at the beginning of the routine, XOR A.
ld b, FIRES
ld hl, enemiesFire
refreshEnemiesFire_loopCount:
bit $07, (hl)
jr z, refreshEnemiesFire_end
inc a
refreshEnemiesFire_loopCountCont:
inc hl
inc hl
djnz refreshEnemiesFire_loopCount
refreshEnemiesFire_end:
ld (enemiesFireCount), a
ret
We load the maximum number of shots in B, LD B, FIRES, and aim HL at its setting, LD HL, enemiesFire.
Evaluate if the fire is active, BIT $07, (HL), and jump if not, JR Z, refreshEnemiesFire_end.
If active, we increment A to add an active fire, INC A, point HL to the first byte of the next fire, INC HL, INC HL, and continue the loop until the value of B becomes zero, DJNZ refreshEnemiesFire_loopCount.
Finally, we update in memory the number of shots still active, LD (enemiesFireCount), A, and exit, RET.
The final aspect of the routine is as follows:
; -------------------------------------------------------------------
; Updates enemy shots settings
;
; Alters the value of the AD, BC, HL and IX registers.
; -------------------------------------------------------------------
RefreshEnemiesFire:
ld b, FIRES ; B = maximum number of shots
xor a ; A = 0
refreshEnemiesFire_loopExt:
push bc ; Preserve BC
ld ix, enemiesFire ; IX = config shots
ld b, FIRES ; B = maximum number of shots
refreshEnemiesFire_loopInt:
bit $07, (ix+$00) ; Active shot?
jr nz, refreshEnemiesFire_loopIntCont ; Active, jumps
ld c, (ix+$02) ; C = byte 1 next shot
ld (ix+$00), c ; Byte 1 of the current = C
ld c, (ix+$03) ; C = byte 2 next shot
ld (ix+$01), c ; Byte 2 of the current = C
ld (ix+$02), a ; Byte 1 next shot = 0
refreshEnemiesFire_loopIntCont:
inc ix
inc ix ; IX = byte 1 next shot
djnz refreshEnemiesFire_loopInt ; Loop until B = 0
pop bc ; Retrieves BC (outer loop)
djnz refreshEnemiesFire_loopExt ; Loop until B = 0
; Updates the number of active shots
ld b, FIRES ; B = maximum number of shots
ld hl, enemiesFire ; HL = fire configuration
refreshEnemiesFire_loopCount:
bit $07, (hl) ; Active shot?
jr z, refreshEnemiesFire_end ; Not active, skips
inc a ; A=A+1 (shot counter)
refreshEnemiesFire_loopCountCont:
inc hl
inc hl ; HL = byte 1 next shot
djnz refreshEnemiesFire_loopCount ; Loop until B = 0
refreshEnemiesFire_end:
ld (enemiesFireCount), a ; Update shot counter
ret
Next, we implement the routine that triggers the shots. The shots will be fired when the enemy is in the same horizontal coordinate as the ship and when they are not all active.
We continue in game.asm, locate the MoveEnemies tag and implement the trigger activation routine on top of it.
EnableEnemiesFire:
ld de, (shipPos)
ld hl, enemiesConfig
ld b, ENEMIES
We load in DE the position of the ship, LD DE, (shipPos), point HL to the address of the enemies configuration, LD HL, enemiesConfig, and we load in B the maximum number of enemies, LD B, ENEMIES.
enableEnemiesFire_loop:
ld a, (enemiesFireCount)
cp FIRES
ret nc
push bc
ld a, (hl)
ld b, a
inc hl
and $80
jr z, enableEnemiesFire_loopCont
ld a, (hl)
and $1f
cp e
jr nz, enableEnemiesFire_loopCont
We load into register A the number of active shots, LD A, (enemiesFireCount), compare it with the maximum number of shots, CP FIRES, and quit when we have reached it, RET NC.
We keep the value of BC, PUSH BC, load the first byte of the enemy configuration in A, LD A, (HL), load it in B, LD B, A, point HL to the second byte, INC HL, see if the enemy is active, AND $80, and if not jump, JR Z, enableEnemiesFire_loopCont.
If the enemy is active, we load the second byte of the configuration into A, LD A, (HL), keep the X-coordinate, AND $1F, compare with the X-coordinate of the ship, CP E, and skip if they are not the same, JR NZ, enableEnemiesFire_loopCont.
If we have not jumped, we need to enable the shot.
ld c, a
push hl
push bc
ld hl, enemiesFire
ld a, (enemiesFireCount)
add a, a
ld b, $00
ld c, a
add hl, bc
pop bc
ld (hl), b
inc hl
ld (hl), c
ld hl, enemiesFireCount
inc (hl)
pop hl
We load the enemy’s x-coordinate into C, LD C, A, and we have the firing configuration. Preserve HL, PUSH HL, preserve BC, PUSH BC, point HL to the enemy shots configuration, LD HL, enemiesFire, load into A the number of active shots, LD A, (enemiesFireCount), multiply by two, ADD A, A, set B to zero, LD B, $00, load into C the number of bytes to move, LD C, A, and add it to HL so that it points to the position in the list where we are going to set the shot configuration, ADD HL, BC.
We retrieve the shot configuration, POP BC, load the first byte into memory, LD (HL), B, point HL to the second byte in the list, INC HL, load the second byte into memory, LD (HL), C, point HL to the shots counter, LD HL, enemiesFireCount, increment it, INC (HL), and retrieve HL to point to the second byte of the enemy configuration, POP HL.
enableEnemiesFire_loopCont:
pop bc
inc hl
djnz enableEnemiesFire_loop
ret
We get the value of BC, get the loop counter, POP BC, point HL to the first byte of the next enemy configuration, INC HL, and keep looping, DJNZ enebleEnemiesFire_loop, until we have looped through all the enemies. Finally we exit, RET.
The final aspect of the routine is as follows:
; -------------------------------------------------------------------
; Enables enemy fire.
;
; Alters the value of the AF, BC, DE and HL registers.
; -------------------------------------------------------------------
EnableEnemiesFire:
ld de, (shipPos) ; DE = ship position
ld hl, enemiesConfig ; HL = enemiesConfig
ld b, ENEMIES ; B = total number of enemies
enableEnemiesFire_loop:
ld a, (enemiesFireCount) ; A = number of active shots
cp FIRES ; Compares with max. shots
ret nc ; Reached, exits (NC)
push bc ; Preserve BC
ld a, (hl) ; A = 1st byte enemy config
ld b, a ; B = A
inc hl ; HL = 2nd byte config
and $80 ; Active enemy?
jr z, enableEnemiesFire_loopCont ; Not active, skip
ld a, (hl) ; A = 2nd byte enemy config
and $1f ; A = coord X
cp e ; Compare with ship
jr nz, enableEnemiesFire_loopCont ; Not equal, skip
; Activate the shot
; The shot configuration is that of the enemy
ld c, a ; C = enemy coord X
push hl ; Preserves HL
push bc ; Preserves BC, config shot
ld hl, enemiesFire ; HL = enemy fire
ld a, (enemiesFireCount) ; A = shots counter
add a, a ; A = A*2, two bytes shot
ld b, $00
ld c, a ; BC = offset
add hl, bc ; HL = HL+BC, shot to activate
pop bc ; BC, config trigger
ld (hl), b ; Load into memory 1st byte config
inc hl ; HL = 2nd byte config
ld (hl), c ; Load in memory
ld hl, enemiesFireCount ; HL = shots counter
inc (hl) ; Increments in memory
pop hl ; HL = 2nd byte config
enableEnemiesFire_loopCont:
pop bc ; B = total number of enemies
inc hl ; HL = 1st byte enemy config next
djnz enableEnemiesFire_loop ; Until it runs through all the enemies
; B = 0
ret
Shots is enabled when the enemies are in the same horizontal coordinate as the ship, so it’s called from within the MoveEnemies routine.
In MoveEnemies we will change two things: first we go to the moveEnemies_cont tag, and the second line, which now looks like this:
ld d, $14 ; D = total number of enemies (20)
We leave it at that:
ld d, ENEMIES ; D = total number of enemies
Earlier we declared the constant ENEMIES, and now we need to reference it in all the places where the number of enemies is loaded.
Look for moveEnemies_end and after the first line:
call PrintEnemies ; Print Enemies
We add the EnableEnemiesFire call:
call EnableEnemiesFire ; Enables enemy fire
We implement a routine for moving enemy shots, just as we have one for moving enemies.
We continue in game.asm, locate MoveFire and implement the routine that moves the enemy shots just before it.
MoveEnemiesFire:
ld a, $03
call Ink
ld hl, flags
bit $04, (hl)
ret z
res 04, (hl)
We load in A the magenta ink, LD A, $03, and change it, CALL Ink. We load the flags in HL, LD HL, flags, and check if bit four is active, BIT $04, (HL). If the bit is not set, we exit, RET Z, otherwise we disable it, RES $04, (HL).
As you may have noticed, we are going to use another bit of flags.
ld d, FIRES
ld hl, enemiesFire
moveEnemiesFire_loop:
ld b, (hl)
inc hl
ld c, (hl)
dec hl
We load the maximum number of shots into D, LD D, FIRES, point HL to the shot configuration, LD HL, enemiesFire, load the first byte into B, LD B, (HL), point HL to the second byte, INC HL, load it into C, LD C, (HL), and point HL back to the first byte, DEC HL.
bit $07, b
jr z, moveEnemiesFire_loopCont
res $07, b
call DeleteChar
ld a, ENEMY_TOP_B + $01
cp b
jr z, moveEnemiesFire_loopCont
dec b
call At
ld a, ENEMY_GRA_F
rst $10
set $07, b
We evaluate if the shot is active, BIT $07, B, and jump if it is not, JR Z, moveEnemiesFire_loopCont. If it’s inactive, we could exit the routine, but we don’t, so that the routine always takes the same time to execute, or at least as close as possible between each execution.
If it is active, we keep the Y-coordinate, RES $07, B, delete the fire from its current position, CALL DeleteChar, load the vertical stop of the fire from below in A, LD A, ENEMY_TOP_B+$01, compare with the Y-coordinate, CP B, and jump, JR Z, moveEnemiesFire_loopCont, if we have reached it.
If we have not reached the top, we set the Y-coordinate to the next line, DEC B, position the cursor, CALL At, load the graph of the enemy shot in A, LD A, ENEMY_GRA_F, draw it, RST $10, and leave the shot activated, SET $07, B.
moveEnemiesFire_loopCont:
ld (hl), b
inc hl
inc hl
dec d
jr nz, moveEnemiesFire_loop
jp RefreshEnemiesFire
At this point we have enabled or disabled the shot and updated the Y coordinate accordingly. We update the first byte of the in-memory configuration, LD (HL), D, point HL to the first byte of the next shot, INC HL, INC HL, decrement D where we have the number of iterations of the loop, DEC D, and continue, JR NZ, moveEnemiesFire_loop, until D is zero.
Finally, we jump to refresh the shot list and exit, JP RefreshEnemiesFire.
The final aspect of the routine is as follows:
; -------------------------------------------------------------------
; Moves the enemy's shot.
;
; Alters the value of the AF, BC, DE and HL registers.
; -------------------------------------------------------------------
MoveEnemiesFire:
ld a, $03 ; A = ink 3
call Ink ; Change ink
ld hl, flags ; HL = flags
bit $04, (hl) ; Active move enemy shot?
ret z ; Not active, exits
res $04, (hl) ; Deactivates flag move shot
ld d, FIRES ; D = maximum number of shots
ld hl, enemiesFire ; HL = enemy shot
moveEnemiesFire_loop:
ld b, (hl) ; B = coord Y shot
inc hl ; HL = coord X
ld c, (hl) ; C = coord X
dec hl ; HL = coord Y
bit $07, b ; Active shot?
jr z, moveEnemiesFire_loopCont ; Not active, skip
res $07, b ; B = coord Y
call DeleteChar ; Delete shot
ld a, ENEMY_TOP_B + $01 ; A = limit at the bottom
cp b ; Compare with coord Y
jr z, moveEnemiesFire_loopCont ; Equals, jump
dec b ; B = next line
call At ; Position cursor
ld a, ENEMY_GRA_F ; A = shot graph
rst $10 ; Paints it
set $07, b ; Activates shot
moveEnemiesFire_loopCont:
ld (hl), b ; Update coord Y shot
inc hl
inc hl ; HL = 1st byte enemy config next
dec d ; D = D - 1
jr nz, moveEnemiesFire_loop ; Loop until D = 0
jp RefreshEnemiesFire ; Refreshes shots and exits
We are almost ready to see enemy fire on the screen.
At the start of the MoveEnemies routine, we get the value of the flags tag and evaluate whether bit four is set.
We go to Main.asm and add the following to the flags comments:
; Bit 4 -> move enemy shot 0 = No, 1 = Yes
We continue in Main.asm and take the opportunity to include the calls to some of the routines we have implemented.
We locate the Main_start tag and, before CALL ChangeLevel, we include the call to initialise the shots:
call ResetEnemiesFire
We locate the Main_loop routine and, between CALL MoveEnemies and CALL CheckCrashShip, we add the call to the routine that moves the enemy shots:
call MoveEnemiesFire
We’ll take this opportunity to comment out the CALL CheckCrashShip line so that we don’t get killed by enemies and we can see what the shots look like.
Finally, we find the Main_restart routine and almost at the end, just before CALL Sleep, we add another call to initialise enemy shots:
call ResetEnemiesFire
We’re done in main.asm, but we still need to set bit four of the flags to make everything work.
Let’s go to int.asm, and the first thing we need to do is decide what speed the enemy shot will move at. There is no need to implement anything new to have two speeds available:
- The speed at which the ship is moving.
- The speed at which enemies move.
I chose the second one. Find the line SET $02, (HL), and add just below it:
set $04, (hl)
If you want it to move at the speed of the ship, this line should be placed just below SET $00, (HL).
We have implemented a good number of lines. It’s time to test and see the results; we’ll compile, load and see what happens.
If all goes well, you can already see the enemy shots.
I commented that five shots at once might be too much. To get a better idea, we located MoveEnemies on game.asm and commented on the CALL PrintEnemies line towards the end to see it better.
We compile, load into the emulator and see the results.
If we add the enemies, it might be too much. We uncomment the CALL PrintEnemies line, and in main.asm, in the MainLoop routine, we find the CALL CheckCrashShip line and remove the comment.
We compile, load and see that the enemies kill us again. The only thing left to do is to make the enemy shoot at us.
Before implementing the collisions between the ship and enemy shots, remember that we declared a constant with the total number of enemies, ENEMIES, but we still have parts of the code where we do not use it.
We go to print.asm, locate PrintEnemies and modify the line LD D, $14 as follows:
ld d, ENEMIES
The rest of the changes are made in game.asm.
We locate the ChangeEnemies routine, locate the LD B, $14 line and modify it accordingly:
ld b, ENEMIES
Find the CheckCrashFire routine and delete the lines:
ld b, enemiesConfigEnd - enemiesConfigIni
sra b
And we replace them with:
ld b, ENEMIES
We make the same change to the CheckCrashShip routine.
And now we implement the collisions between the ship and the enemy shots. We continue in the CheckCrashShip routine, go to the end and just before RET we add the new collisions.
checkCrashShipFire:
ld de, (shipPos)
ld a, (enemiesFireCount)
ld b, a
ld hl, enemiesFire
We load into DE the position of the ship, LD DE, (shipPos), into A the number of shots fired, LD A, (enemiesFireCount), then into B, LD B, A, and point HL to the shots configuration, LD HL, enemiesFire.
checkCrashShipFire_loop:
ld a, (hl)
inc hl
res $07, a
cp d
jr nz, checkCrashShipFire_loopCont
ld a, (hl)
cp e
jr nz, checkCrashShipFire_loopCont
We load the first byte of the configuration into A, LD A, (HL), point HL to the second byte, INC HL, leave the Y-coordinate, RES $07, A, compare it with the ship’s coordinate, CP D, and skip if they are not the same, JR NZ, checkCrashShipFire_loopCont.
If the coordinates are the same, we load into A the X coordinate of the shot, LD A, (HL), compare it with that of the ship, CP E, and jump if they are not the same, JR NZ, checkCrashShipFire_loopCont.
dec hl
res 07, (hl)
ld a, (livesCounter)
dec a
daa
ld (livesCounter), a
call PrintInfoValue
call PrintExplosion
jp RefreshEnemiesFire
If there is a collision of the shot with the ship, we point HL to the first byte of the shots configuration, DEC HL, disable the shot, RES $07, (HL), load the lives into A, LD A, (livesCounter), remove one, DEC A, do the decimal adjustment, DAA, and update in memory, LD (livesCounter), A.
We print the game information, CALL PrintInfoValue, paint the explosion, CALL PrintExploxion, and refresh the enemy shot list and exit that way, JP RefreshEnemiesFire.
checkCrashShipFire_loopCont:
inc hl
djnz checkCrashShipFire_loop
If there was no collision, point HL to the first byte of the next shot configuration, INC HL, and loop until all shots have been traversed, DJNZ checkCrashShipFire_loop.
The final aspect of collision detection between the ship and enemies (enemy ships and shots) is as follows:
; -------------------------------------------------------------------
; Evaluates enemy collisions and shots 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, ENEMIES ; B = number of enemies
checkCrashShip_loop:
ld a, (hl) ; A = enemy Y-coordinate
inc hl ; HL = enemy coord X
bit $07, a ; Enemy active?
jr z, checkCrashShip_endLoop ; Not active, skips
and $1f ; A = coord Y enemy
cp d ; Compare with ship
jr nz, checkCrashShip_endLoop ; Not the same, skip
ld a, (hl) ; A = enemy X coord
and $1f ; A = coord X
cp e ; Compare ship
jr nz, checkCrashShip_endLoop ; Not the same, skip
dec hl ; HL = coord Y enemy
res $07, (hl) ; Deactivates enemy
ld a, (enemiesCounter) ; A = number of enemies
dec a ; Subtract one
daa ; Decimal adjust
ld (enemiesCounter), a ; Updates in memory
ld a, (livesCounter) ; A = lives
dec a ; Remove one
daa ; Decimal adjust
ld (livesCounter), a ; Update in memory
call PrintInfoValue ; Paint info. value
jp PrintExplosion ; Paint explosion and it comes out
checkCrashShip_endLoop:
inc hl ; HL = coord Y next enemy
djnz checkCrashShip_loop ; Loop until B = 0
checkCrashShipFire:
; Checks for collisions between enemy shot and ship
ld de, (shipPos) ; DE = ship position
ld a, (enemiesFireCount)
ld b, a ; B = number of active shots
ld hl, enemiesFire ; HL = shots configuration
checkCrashShipFire_loop:
ld a, (hl) ; A = coord Y shot
inc hl ; HL = coord X
res $07, a ; A = coord Y
cp d ; Compare with ship
jr nz, checkCrashShipFire_loopCont ; Distinct, skip
ld a, (hl) ; A = coord X shot
cp e ; Compare with ship
jr nz, checkCrashShipFire_loopCont ; Distinct, skip
; If it gets here, the ship has collided with the shot.
dec hl ; HL = 1st byte of config
res $07, (hl) ; Deactivate shot
ld a, (livesCounter) ; A = lives
dec a ; Removes one
daa ; Decimal adjust
ld (livesCounter), a ; Update in memory
call PrintInfoValue ; Paint info. value
call PrintExplosion ; Paint Explosion
jp RefreshEnemiesFire ; Refreshes shots and exits
checkCrashShipFire_loopCont:
inc hl ; HL = next shot
djnz checkCrashShipFire_loop ; Loop until B = 0
ret
Now we have the enemy shot. Compile, load into the emulator and see the results.
Difficulty setting
Maybe the difficulty is too high now, maybe not. Either way, let’s look at some small changes we can make to adjust the difficulty.
The changes I am suggesting are for you to test, but do not leave them permanently, as we will later add an option in the menu for the player to choose between different levels of difficulty.
The first way to reduce the difficulty is to reduce the speed at which enemies move and shoot. Locate the line SUB $03 in int.asm and replace $03 with $04, $05, $06, etc. Remember that the higher this number is, the slower the enemies will move. Try it and you will see how it reduces.
We can reduce the difficulty by reducing the number of simultaneous shots. Go into the const.asm file, find the FIRES tag and change its value to $01, $02, etc. We compile and see how the difficulty is reduced as there are fewer simultaneous shots.
We can also reduce the difficulty if the enemies and the ship do not collide. We locate the moveEnemies_Y_down tag and two lines down we have SUB ENEMY_TOP_B, we modify this line and leave it as follows:
sub ENEMY_TOP_B + $01
As you can see, the enemies and the ship no longer collide, which reduces the difficulty. If this reduces the difficulty too much, increase the number of simultaneous shots.
By not colliding with the ship, we could save a lot of the CheckCrashShip routine, but as we are going to change this based on player selection, we will leave it as it is.
Another way to reduce the difficulty is a la Galactic Plague, the first game I loaded on my Amstrad CPC 464, where you have three lives to complete each level.
To start each level with five lives, go to main.asm, locate Main_restart, and add the following lines before CALL FadeScreen:
ld hl, livesCounter
ld (hl), $05
With these lines, we will have five lives at the start of each level.
ZX Spectrum Assembly, Space Battle
We’ve changed the behaviour of the enemies, we’ve given them a shot and we’ve also looked at different ways of adjusting the difficulty.
In the next chapter of ZX Spectrum Assembly, we will add in-game music and sound effects.
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.