ZX Spectrum Assembly, Space Battle – 0x0A Joystick and extra life
In this chapter of ZX Spectrum Assembly, we will implement joystick control and get an extra life every five hundred points.
We create the folder Step10 and copy the files loader.tap, const.asm, ctrl.asm, game.asm, graph.asm, int.asm, main.asm, make or make.bat, print.asm and var.asm from the folder Step09.
Translation by Felipe Monge Corbalán
Table of contents
Delay
First we implemented a delay between levels to give us time to prepare.
We will open game.asm and at the end of it we will implement the routine that will produce about half a second of delay. The ULA produces fifty interrupts per second on PAL systems, sixty on NTSC. We will implement a loop that waits for twenty-five interrupts.
; -------------------------------------------------------------------
; Wait for twenty-five interruptions.
; -------------------------------------------------------------------
Sleep:
ld b, $19 ; B = 25
sleep_Loop:
halt ; Wait for interruption
djnz sleep_Loop ; Loop until B = 0
ret
We won’t explain the code, you already have enough knowledge to understand it.
To see how this routine works, open main.asm, locate the Main_start tag, and at the end, just after CALL PrintEnemies, add the call to the delay routine.
call Sleep
Locate Main_restart and at the end, before JR Main_loop, add the following lines:
call PrintEnemies
call Sleep
Now we compile, load into the emulator and see that there is a delay between the time the enemies beep and the time they move.
Joystick
Since we are going to use the joystick to control the game, we have three other control options in addition to the buttons, and we need to store somewhere the type of control the player has chosen. We open var.asm, locate enemiesCounter and add a new label just above it:
controls:
db $00
This is where we will store the player’s choice of controls.
Open print.asm and locate printFirstScreen_op. We will delete the lines BIT $00, A and JR NZ, printFirstScreen_op. We will replace them with the new implementation. We will leave the rest of the lines as they are and add them just above CALL FadeScreen:
printFirstScreen_end:
ld a, b
ld (controls), a
We have added a new tag, printFirstScreen_end, and as you can see we have selected the controls in B, we load them into A, LD A, B, and from there we load them into memory, LD (controls), A.
We implement the rest of the routine in the place where the deleted lines were, just below the keyboard display, IN A, ($FE).
ld b, $01
rra
jr nc, printFirstScreen_end
inc b
rra
jr nc, printFirstScreen_end
inc b
rra
jr nc, printFirstScreen_end
inc b
rra
jr c, printFirstScreen_op
It should be remembered that when reading the keyboard, the status of the keys is given in bits zero to four, where bit zero corresponds to the key furthest from the centre of the keyboard and bit four corresponds to the key closest to the centre of the keyboard. Similarly, the bit is set to zero if the key has been pressed and to one if it has not.
We set B to one, the key option, LD B, $01, rotate A to the right, set the value of the zero bit (key 1) in the carry flag, RRA, and if the carry flag is disabled, the bit has been set to zero, the key has been pressed and we jump, JR NC, printFirstScreen_end, because they have selected keyboard.
If carry is enabled, we increment B to two (Kempston), rotate by setting the value of the zero bit (key 2 after the previous rotation) in the carry flag, RRA, and jump as before, JR NC, printFirstScreen_end, if carry is disabled.
If 2 has not been pressed, we rotate and check keys 3 and 4, paying attention to the last JR, in this case JR C, printFirstScreen_op. If 4 has not been pressed either, the carry is active and we read the keyboard and continue the loop until any key from 1 to 4 is pressed.
The final aspect of the routine is as follows:
; -------------------------------------------------------------------
; Display screen and selection of controls.
;
; Alters the value of the AF and HL registers.
; -------------------------------------------------------------------
PrintFirstScreen:
call CLS ; Clear screen
ld hl, title ; HL = title definition
call PrintString ; Paint title
ld hl, firstScreen ; HL = screen definition
call PrintString ; Paint screen
printFirstScreen_op:
ld a, $f7 ; A = half-row 1-5
in a, ($fe) ; Read keyboard
ld b, $01 ; B = 1, option keys
rra ; Rotate A right
jr nc, printFirstScreen_end ; Carry? No, pressed
inc b ; B = B+1, option Kempston
rra ; Rotate A right
jr nc, printFirstScreen_end ; Carry? No, pressed
inc b ; B = B+1, option Sinclair 1
rra ; Rotate A right
jr nc, printFirstScreen_end ; Carry? No, pressed
inc b ; B = B+1, option Sinclair 2
rra ; Rotate A right
jr c, printFirstScreen_op ; Carry? Yes, not pressed
printFirstScreen_end:
ld a, b ; A = selected option
ld (controls), a ; Load into memory
call FadeScreen ; Fade screen
ret
Now you need to use the controls you have chosen, and the first thing you need to know is how to read the joysticks.
In the case of the Sinclair joysticks, each joystick is mapped to a half row of the keyboard, which is not the case with the Kempston. Another difference is that the Sinclair joysticks set the pressed directions to zero, whereas the Kempston joysticks set them to one.
Below is a table detailing how to read the joystick keystrokes and in which bit we have each address.
Joystick | Half-row | Port | Up | Below | Left | Right. | Fire |
Sinclair 1 | $EF(0-6) | $FE | 1 | 2 | 4 | 3 | 0 |
Sinclair 2 | $F7(1-5) | $FE | 3 | 2 | 0 | 1 | 4 |
Kempston | $1F | 3 | 2 | 1 | 0 | 4 |
We open ctrl.asm and modify CheckCtrl to take into account the four types of controls available.
The first line of this routine is LD D, $00, and just below this we will implement the management of the controls. We delete from just below LD D, $00 to just above RET as follows:
CheckCtrl:
ld d, $00 ; D = 0
ret
At the end of the routine it checked if both left and right were pressed at the same time, checkCtrl_testLR, and if so both were skipped. We will remove this check because if both are pressed the ship will move to the right (see MoveShip in game.asm) and by removing this part we save ten bytes and thirty-eight or forty-four clock cycles.
And now we start the implementation right after LD D, $00.
ld a, (controls)
dec a
jr z, checkCtrl_Keys
dec a
jr z, checkCtrl_Kempston
dec a
jr z, checkCtrl_Sinclair1
We load into A the selected controls, a value between one and four, LD A, (controls), and decrement A, DEC A. If the value of A was one, after decrementing it is zero and we jump, JR Z, checkCtrl_Keys. If the keyboard was not selected, we decrement A and check if Kempston was selected, and if not we do the same to see if Sinclair 1 was selected. If neither has been selected, then Sinclair 2 has been selected.
Previously we checked if a key was pressed with the instruction BIT n, r, which takes two bytes and eight clock cycles. Since a single read of the port gives us the status of all addresses, this time we will use rotations of register A, which occupy one byte and take four clock cycles. We use a maximum of five rotations, occupying five bytes and taking twenty clock cycles. The alternative is to use three BIT instructions, occupying six bytes and taking twenty-eight clock cycles; with rotations we save bytes and clock cycles.
checkCtrl_Sinclair2:
ld a, $f7
in a, ($fe)
checkCtrl_Sinclair2_left:
rra
jr c, checkCtrl_Sinclair2_right
set $00, d
checkCtrl_Sinclair2_right:
rra
jr c, checkCtrl_Sinclair2_fire
set $01, d
checkCtrl_Sinclair2_fire:
and $04
ret nz
set $02, d
ret
We load the half stack 1-5 into A, LD A, $F7, and read the keyboard, IN A, ($FE). We rotate A to the right to see if the left direction, RRA, has been pressed, and if not, the carry flag is set and jumps, JR C, chechCtrl_Sinclair2_right. If pressed, we set the zero bit of D, SET $00, D.
We rotate A to the right to check if the right direction, RRA, has been pressed, and if not, the carry is activated and jumps, JR C, chechCtrl_Sinclair2_fire. If it has been pressed, we set bit one of D, SET $01, D.
Now the shot is in bit two, check if it is set, AND $04, and exit if it is not, RET NZ. If it is, we activate bit two of D, SET $02, D, and exit, RET.
We will now manage the Kempston selection.
checkCtrl_Kempston:
in a, ($1f)
checkCtrl_Kempston_right:
rra
jr nc, checkCtrl_Kempston_left
set $01, d
checkCtrl_Kempston_left:
rra
jr nc, checkCtrl_Kempston_fire
set $00, d
checkCtrl_Kempston_fire:
and $04
ret z
set $02, d
ret
We read port thirty-one, IN A, ($1F). We rotate A to the right to check if the right direction, RRA, has been pressed and turn off the carry and jump, JR NC, chechCtrl_Kempston_left, if it has not been pressed. If it was pressed, we set bit one of D, SET $01, D.
We rotate A to the right to check if the left direction, RRA, has been pressed and if not, the carry flag is disabled and jumps, JR NC, chechCtrl_Kempston_fire. If it was pressed, we set bit one of D, SET $00, D.
Now the shot is in bit two, we check if it is pressed, AND $04, and if not, RET Z. If it is pressed, we activate bit two of D, SET $02, D, and exit, RET.
The management of Sinclair 1 and the keyboard is the same as for Sinclair 2, only the order of the tests is different, so let’s look at the last aspect of the routine.
; -------------------------------------------------------------------
; Evaluates whether an direction has been clicked.
; Kempston, Sinclair 1 and Sinclair 2
; The keys are:
; Z -> Left
; X -> Right
; V -> Trigger
;
; Return: D -> Keys pressed:
; Bit 0 -> Left
; Bit 1 -> Right
; Bit 2 -> Trigger
;
; Alters the value of the registers A and D
; -------------------------------------------------------------------
CheckCtrl:
ld d, $00 ; Sets D to 0
ld a, (controls) ; A = selection controls
dec a ; A = A-1
jr z, checkCtrl_Keys ; Zero, skip
dec a ; A = A-1
jr z, checkCtrl_Kempston ; Zero, skip
dec a ; A = A-1
jr z, checkCtrl_Sinclair1 ; Zero, skip
; Sinclair 2 control
checkCtrl_Sinclair2:
ld a, $f7 ; A = half-row 1-5
in a, ($fe) ; Read keyboard
checkCtrl_Sinclair2_left:
rra ; Rotate A, check left
jr c, checkCtrl_Sinclair2_right ; Carry, not pressed, skip
set $00, d ; No carry, set bit left
checkCtrl_Sinclair2_right:
rra ; Rotate A, check der
jr c, checkCtrl_Sinclair2_fire ; Carry, not pressed, skip
set $01, d ; No carry, set right bit
checkCtrl_Sinclair2_fire:
and $04 ; Check shot
ret nz ; Non-zero, not pressed, exits
set $02, d ; If zero, set shot bit
ret ; Exits
; Kempston control
checkCtrl_Kempston:
in a, ($1f) ; Read port 31
checkCtrl_Kempston_right:
rra ; Rotate A, check right
jr nc, checkCtrl_Kempston_left ; No carry, not pressed, skip
set $01, d ; Carry, set right bit
checkCtrl_Kempston_left:
rra ; Rotate A, check left
jr nc, checkCtrl_Kempston_fire ; No carry, not pressed, skip
set $00, d ; Carry, set left bit
checkCtrl_Kempston_fire:
and $04 ; Check shot
ret z ; Zero, not pressed, exits
set $02, d ; Non-zero, set shot bit
ret ; Exits
; Sinclair 1 control
checkCtrl_Sinclair1:
ld a, $ef ; A = half-row 0-6
in a, ($fe) ; Read keyboard
checkCtrl_Sinclair1_fire:
rra ; Rota A, check shot
jr c, checkCtrl_Sinclair1_right ; Carry, not pressed, skip
set $02, d ; No carry, set bit shot
checkCtrl_Sinclair1_right:
rra
rra
rra ; Rotate A, check right
jr c, checkCtrl_Sinclair1_left ; Carry, not pressed, skip
set $01, d ; No carry, set right bit
checkCtrl_Sinclair1_left:
rra ; Rotate A, check left
ret c ; Carry, not pressed, exit
set $00, d ; No carry, set left bit
ret ; Exits
; Keyboard control
checkCtrl_Keys:
ld a, $fe ; A = half-stack Cs-V
in a, ($fe) ; Read keyboard
checkCtrl_Key_left:
rra
rra ; Rotate A, check left
jr c, checkCtrl_right ; Carry, not pressed, skip
set $00, d ; No carry, set bit left
checkCtrl_right:
rra ; Rotate A, check right
jr c, checkCtrl_fire ; Carry, not pressed, skip
set $01, d ; No carry, set right bit
checkCtrl_fire:
and $02 ; Check shot
ret nz ; Non-zero, not pressed, exits
set $02, d ; Zero, set shot bit
ret ; Exits
We compile, load in the emulator and test the different controls.
Extra life
We’re going to implement that every five hundred fucks you get, you get an extra life.
We open var.asm, locate pointsCounter, and just below it we add a new label:
extraCounter:
dw $0000
In extraCounter we control the accumulation of points until it reaches five hundred to give an extra life. We initialise extraCounter at the start of each game.
We go to the main.asm file, locate the Main_start tag, and look at the first few lines:
xor a
ld hl, enemiesCounter
ld (hl), $20
inc hl
ld (hl), a ; $1d
inc hl
ld (hl), a ; $29
inc hl
ld (hl), $05
inc hl
ld (hl), a
inc hl
ld (hl), a
In this part we initialise the values of the game, which occupies seventeen bytes and takes ninety-two clock cycles. The pair INC HL and LD (HL), A, occupies two bytes and takes thirteen clock cycles. Since we would have to add two more pairs to initialise the two new bytes we added with the extraCounter tag, we would add four bytes and twenty-six clock cycles, for a total of twenty-one bytes and one hundred and eighteen clock cycles, plus the code grows repetitively.
Instead of initialising the values as we do now, we will use the LDIR instruction. We delete the code we used to initialise the values and replace it with the following:
ld hl, enemiesCounter
ld de, enemiesCounter + 1
ld (hl), $00
ld bc, $08
ldir
ld a, $05
ld (livesCounter), a
We point HL to the location of the enemies counter, LD HL, enemiesCounter, and point DE to the next location.
We set the memory location to which HL points to zero, LD(HL), $00, load the number of locations to be set to zero in addition to the first into BC, LD BC, $08, and set the remaining memory locations to zero, LDIR.
Not all values start at zero, lives are done at five, so we load five into A, LD A, $05, and load them into memory, LD (livesCounter), A.
The way we have implemented the initialisation, the code occupies eighteen bytes and takes eighty-one clock cycles, so we have gained bytes and processing time. The code is more readable, and if we need to add more bytes to initialise, all we have to do is change the value of BC.
The final appearance of Main_start is as follows:
Main_start:
ld hl, enemiesCounter
ld de, enemiesCounter + 1
ld (hl), $00
ld bc, $08
ldir
ld a, $05
ld (livesCounter), a
call ChangeLevel
All that’s left is the last part, which accumulates points in extraCounter, gives an extra life and resets the counter to zero when you reach five hundred.
Open game.asm, find the CheckCrashFire tag and scroll to the end of it; it looks like this:
ld (pointsCounter + 1), a ; Update in memory
call PrintInfoValue ; Print InfoValue ; Print InfoValue
ret ; Exits
checkCrashFire_endLoop:
inc hl ; HL = coord Y next enemy
djnz checkCrashFire_loop ; Loop as long as B > 0
ret
The part where we accumulate the points to get the extra life is between LD (pointsCounter + 1), A and CALL PrintInfoValue, so we continue:
ld hl, (extraCounter)
ld bc, $0005
add hl, bc
ld (extraCounter), hl
ld bc, $01f4
sbc hl, bc
jr nz, checkCrashFire_cont
ld (extraCounter), hl
ld a, (livesCounter)
inc a
daa
ld (livesCounter), a
checkCrashFire_cont:
If you have reached this part of the routine, it is because you have hit an enemy and scored five points.
We load the extra life counter into HL, LD HL, (extraCounter), load the five points to be added into BC, LD BC, $0005, add it to HL, ADD HL, BC, and update it in memory, LD (extraCounter), HL.
We load five hundred into BC, LD BC, $01F4, subtract it from HL, SBC HL, BC, and if the result is not zero, we jump because we have not reached five hundred points, JR NZ, checkCrashFire_cont. If the result of the subtraction was zero, we would have reached five hundred points.
SBC is subtraction with carry, the only one available to the Z80 when working with 16-bit registers. It is very important that the carry is disabled, which we know it is because before the subtraction we added five to HL and in our case the value of HL will never exceed five hundred.
If we had not jumped, the value of HL would have reached five hundred and would now be zero. We update the counter in memory by setting it to zero, LD (extraCounter), HL, load the number of lives we have left in A, LD A, (livesCounter), increment A to have one more life, INC A, do the decimal adjustment, DAA, and update the value in memory, LD (livesCounter), A.
Finally, before CALL PrintInfoValue, we set the label to jump to if five hundred is not reached, checkCrashFire_cont.
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 shot?
ret z ; Not active, exits
ld de, (firePos) ; DE = shot position
ld hl, enemiesConfig ; HL = 1st enemy definition
ld b, enemiesConfigEnd-enemiesConfigIni ; B = bytes config enemies
sra b ; B = B/2 number of enemies
checkCrashFire_loop:
ld a, (hl) ; A = enemy Y-coordinate
inc hl ; HL = 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 shot
jr nz, checkCrashFire_endLoop ; Not the same, skip
ld a, (hl) ; A = coord X enemy
and $1f ; A = coord X
cp e ; Compare coord X shot
jr nz, checkCrashFire_endLoop ; Not the same, skip
dec hl ; HL = coord Y enemy
res $07, (hl) ; Deactivates enemy
ld b, d ; B = coord Y shot
ld c, e ; C = coord X shot
call DeleteChar ; Delete shot/enemy
ld a, (enemiesCounter) ; A = number of enemies
dec a ; Subtract one
daa ; Decimal adjust
ld (enemiesCounter), a ; Refresh memory
ld a, (pointsCounter) ; A = units and tens
add a, $05 ; A = A+5
daa ; Decimal adjust
ld (pointsCounter), a ; Refresh memory
ld a, (pointsCounter + 1) ; A hundreds and ud thousands
adc a, $00 ; A = A+1 with carry
daa ; Decimal adjust
ld (pointsCounter + 1), a ; Refresh memory
ld hl, (extraCounter) ; HL = extra life counter
ld bc, $0005 ; BC = 5
add hl, bc ; HL = HL+BC
ld (extraCounter), hl ; Update memory
ld bc, $01f4 ; BC = 500
sbc hl, bc ; HL = HL-BC
jr nz, checkCrashFire_cont ; !0, skip
ld (extraCounter), hl ; 0, extra life counter = 0
ld a, (livesCounter) ; A = lives
inc a ; Add a life
daa ; Decimal adjust
ld (livesCounter), a ; Refresh memory
checkCrashFire_cont:
call PrintInfoValue ; Print InfoValue
ret ; Exits
checkCrashFire_endLoop:
inc hl ; HL = coord Y next enemy
djnz checkCrashFire_loop ; Loop as long as B > 0
ret
We compile, load into the emulator and see the results. Every five hundred points we get an extra life.
To see if it works, we can start the game with extraCounter at $1EF (495) and when we hit an enemy we get a life.
You can also do something that you may have already noticed, if you start the level with the trigger pressed, move to the right and stay there, you will get through almost all the levels without getting killed. This is something we need to change, otherwise you can get through all thirty levels using this technique.
Change of shot
The first thing we will do is change the shot to see if that solves anything. Continue in game.asm, locate MoveFire, and after the first line, LD HL, flags, add the following:
bit 00, (hl)
ret z
We check if the zero bit is active, BIT $00, (HL), and if not we quit.
The zero bit of the flags indicates whether we should move the ship, so now the trigger moves at the same speed as the ship.
We compile, load into the emulator and see the results.
As you can see, the technique of moving to the right no longer works, but I like it better than the shot, which gives a sense of continuity, and also the movement should be polished more, as it does some strange things when there are few enemies left.
We are going to comment on the two lines we added, as we are going to solve them by changing the behaviour of the enemies.
ZX Spectrum Assembly, Space Battle
In this chapter we added a delay for switching between levels, joystick control and extra lives. We also saw a trick to get through all the levels without the slightest effort, and we tried to change the shooting behaviour to avoid it, but we weren’t convinced.
In the next chapter of ZX Spectrum Assembly, we will focus on the behaviour of the enemies.
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.