Viboritas: A 2K game made in 1990

Viboritas updated in action
I had completely forgotten about this game, but fortunately I made backups of my floppy disks for historical record. Recently, I looked at the floppy disk backup index, and I found things as old as 1989, and a name caught my attention: Viboritas (Spanish for little snakes).
This game was coded around 1990, printed, and later saved onto a 5 1/4" floppy disk, then copied again onto a 3 1/2" floppy disk by 1992 when these became mainstream (the image I found), and finally, it was back up around 2011. These backups survived by luck several hard drive crashes till we reach 2024.
I opened the file, extracted the 2K binary, and memories started coming slowly. I even caught a 34 year-old bug.

The history

1990 homebrew computer for students
After doing my first game in Z80 assembler in 1988, I got a lot of confidence in my abilities and went to do several other Z80 programs. However, I lacked access to a proper assembler program, and instead, I coded directly into machine code using a monitor-style program just like shown in the picture at the right, you can even see the Z80 code being typed!
A monitor program was a small application in the ROM of the computer where you had some basic commands like memory listing, writing to memory, and executing your program. Some extras were exit points for your program to show the contents of the Z80 registers and flags.
My father gave again a lecture about computer building in 1990, and I showcased my Karateka game, but I wanted to do something better. I was 11 years old, about to become a teen, and I had a great imagination about impressive games.
My development environment for this game was a homebrew computer for students with a keyboard, a TV for display, and a set of sheets from Zilog with the Z80 mnemonics and respective machine code.
The specifications for this homebrew computer were a Zilog Z80 CPU, 2K of EPROM, 2K of RAM, a TMS9118 VDP, and a Commodore keyboard. You could plug in an expansion board with an AY-3-8910 sound chip that fed from the Z80 clock. The VDP chip, AY chip, and keyboard were readily available because of the 1984 crash.
Students working in the 1990 homebrew computer
Students working in the homebrew computer. You can see a young @nanochess in the front right. Dec/1990.

Into the binary

At the time, I was very inspired by my favorite magazine: Input MSX, in this case issue 12, containing screenshots of a game called Future Knight, and I was in awe imagining how great was it by the screenshots and cover art (later I discovered it is a pretty boring game). In the same issue, there was a BASIC language game called "El Castillo Embrujado" that I already had ported to the BASIC language available in another homebrew computer built by my father.
For this project, I wanted to do a science fiction game in 2K, where the player would use ladders, avoid enemies, and... I had no more. But I was inspired by the ton of ladders in Future Knight. I didn't know what size coding was, but I put the 2K limit in my mind, and the other objective was that the game should be coded directly into the student's computer, now most known as coding in the real hardware.
I didn't envision a final for the game, nor a history, or even a gameplay. After all, I only wanted to have fun developing games, and of course, showcase my game to the students. Notice that having fun developing games isn't the same as developing fun games.
I think that this is my 3rd game in machine code for Z80 processors. The binary came from a 1992 demo disk for students, but it was originally coded in 1990. I only extracted the 2K of the game from the 720K disk image.
The binary of the game looks like this:
Part of the original binary of Viboritas
Given the lack of information about it, I will have to reverse-engineer my own game! The first pass was to fully disassemble it. It sized up to just over one thousand lines of Z80 assembler code but more easily read looking like this:

            ORG $8000

        FNAME "viboritas.bin"

L04CC:      EQU $04CC
L0100:      EQU $0100
L0169:      EQU $0169
L0447:      EQU $0447

L8000:      CALL L04CC
            CALL L801B
            CALL L81BA
L8009:      CALL L8217
L800C:      CALL L8324
            CALL L8504
            JR NC,L800C
L8014:      LD HL,L87FC
            INC (HL)
            JP L8009
I separated the ROM calls, and I don't remember if I have a copy of this computer ROM, but I still remember the function of each call (these are the same as in my first Z80 game). L0100 sets a VDP address (for VRAM or VDP registers), L0169 reads ahead to send data to VRAM, L04CC cleans the screen, and L0447 reads the keyboard. A thing that changed between 1988 and 1990 computers was the port numbers for the VDP.
I made sure the disassembled listing assembles the same binary as the original (using tniASM v0.44). Then I started separately the adaptation for the MSX computers and Colecovision consoles, both having the same video processor, so you can play the game. Just don't expect too much from a kid.

First steps

For starters, I'll reuse the translation layer I made for my Karateka game in Z80 assembler. It will help us to play this old game on an MSX or Colecovision.

	;
	; Viboritas (little snakes)
	;
	; by Oscar Toledo G.
	; (c) Copyright Oscar Toledo G. 1990-2024
	; https://nanochess.org/
	;
	; Creation date: Oct/1990. I was 11 years old.
	; Revision date: Jan/31/2024. Disassembled.
	; Revision date: Feb/01/2024. Ported to MSX/Colecovision.
	;

COLECO: EQU 1   ; Define this to 0 for MSX, 1 for Colecovision

RAM_BASE:	EQU $E000-$7000*COLECO
VDP:		EQU $98+$26*COLECO

PSG:	EQU $FF	; Colecovision

PSG_ADDR:	EQU $A0	; MSX
PSG_DATA:	EQU $A1	; MSX

KEYSEL:	EQU $80
JOYSEL:	EQU $C0
JOY1:	EQU $FC
JOY2:	EQU $FF

    if COLECO
        fname "viboritas_cv.ROM"

	org $8000,$9fff

	dw $aa55	; No BIOS title screen
	dw 0
	dw 0
	dw 0
	dw 0
	dw START

	jp 0		; RST $08
	jp 0		; RST $10
	jp 0		; RST $18
	jp 0		; RST $20
	jp 0		; RST $28
	jp 0		; RST $30
	jp 0		; RST $38

	jp 0		; No NMI handler

    else
        fname "viboritas_msx.ROM"

	org $4000,$5fff

	dw $4241
	dw START
	dw 0
	dw 0
	dw 0
	dw 0
	dw 0
	dw 0

WRTPSG: equ $0093
SNSMAT:	equ $0141

    endif

WRTVDP:
	ld a,b
	out (VDP+1),a
	ld a,c
	or $80
	out (VDP+1),a
	ret

SETWRT:
	ld a,l
	out (VDP+1),a
	ld a,h
	or $40
	out (VDP+1),a
	ret

WRTVRM:
	push af
	call SETWRT
	pop af
	out (VDP),a
	ret

FILVRM:
	push af
	call SETWRT
.1:	pop af
	out (VDP),a
	push af
	dec bc
	ld a,b
	or c
	jp nz,.1
	pop af
	ret

	; Setup VDP before game
setup_vdp:
	LD BC,$0200
	CALL WRTVDP
	LD BC,$C201	; No interrupts
	CALL WRTVDP
	LD BC,$0F02	; $3C00 for pattern table
	CALL WRTVDP
	LD BC,$FF03	; $2000 for color table
	CALL WRTVDP
	LD BC,$0304	; $0000 for bitmap table
	CALL WRTVDP
	LD BC,$3605	; $1b00 for sprite attribute table
	CALL WRTVDP
	LD BC,$0706	; $3800 for sprites bitmaps
	CALL WRTVDP
	LD BC,$0407	; Blue border
	CALL WRTVDP
    IF COLECO
	LD HL,($006C)   ; MSX BIOS chars
	LD DE,-128
	ADD HL,DE
    ELSE
	LD HL,($0004)   ; MSX BIOS chars
	INC H
    ENDIF
        PUSH HL
        LD DE,$0100
        LD BC,$0300
        CALL LDIRVM
        POP HL
        PUSH HL
        LD DE,$0900
        LD BC,$0300
        CALL LDIRVM
        POP HL
        LD DE,$1100
        LD BC,$0300
        CALL LDIRVM

        LD HL,$2000
        LD BC,$1800
        LD A,$F4
        CALL FILVRM
	RET

LDIRVM:
        EX DE,HL
.1:     LD A,(DE)
        CALL WRTVRM
        INC DE
        INC HL
        DEC BC
        LD A,B
        OR C
        JR NZ,.1
        RET

GTTRIG:
    if COLECO
        out (KEYSEL),a
        ex (sp),hl
        ex (sp),hl
        in a,(JOY1)
        ld c,a
        in a,(JOY2)
        and c
        ld c,a
	out (JOYSEL),a
	ex (sp),hl
	ex (sp),hl
	in a,(JOY1)
        and c
        ld c,a
	in a,(JOY2)
	and c
	rlca
	rlca
	ccf
	ld a,0
	sbc a,a
	ret
    else
	xor a
	call $00d8
	or a
	ret nz
	ld a,1
	call $00d8
	or a
	ret nz
        ld a,2
        call $00d8
        or a
        ret nz
        ld a,3
        call $00d8
        or a
        ret nz
        ld a,4
        call $00d8
        ret
    endif

	;
	; Gets the joystick direction
	; 0 - No movement
	; 1 - Up
	; 2 - Up + right
	; 3 - Right
	; 4 - Right + down
	; 5 - Down
	; 6 - Down + left
	; 7 - Left
	; 8 - Left + Up
	;
GTSTCK:
    if COLECO
        out (JOYSEL),a
	ex (sp),hl
	ex (sp),hl
        in a,(JOY1)
	ld b,a
	in a,(JOY2)
	and b
        and $0f
        ld c,a
        ld b,0
        ld hl,joy_map
        add hl,bc
        ld a,(hl)
        ret

joy_map:
        db 0,0,0,6,0,0,8,7,0,4,0,5,2,3,1,0

    else
	xor a
	call $00d5
	or a
	ret nz
	ld a,1
	call $00d5
	or a
	ret nz
	ld a,2
	jp $00d5
    endif

	; ROM routines I forgot

	; Clean screen
L04CC:	; $04cc
	LD HL,$3C00
	LD BC,$0300
	XOR A
	JP FILVRM

	; Select address or register in VDP
L0100:
	LD A,L
	OUT (VDP+1),A
	LD A,H
	ADD A,$40
	OUT (VDP+1),A
	RET


	; Copy string to VDP
L0169:	; $0169
	EX (SP),HL

.0:	LD A,(HL)
	INC HL
	OR A
	JR Z,.1
	PUSH AF
	POP AF
	OUT (VDP),A
	JR .0

.1:	EX (SP),HL
	RET

	;
	; Start of the game
	;
START:		; 8000
	DI			; We don't need interruptions.
	LD SP,L87F0
   if COLECO
	CALL $1FD6		; Turn off sound.
   endif
	CALL setup_vdp		; Not in original but needed to setup VDP.

	ld hl,$7513
	ld (L8780),hl
	ld hl,$983f
	ld (L8782),hl
	ld hl,$c9bf
	ld (L8784),hl
We now start analyzing the code, trying to discover how it works. We'll go forward and backward on the 2K memory map and as I coded directly in machine code, there are no names for labels except for their corresponding address in the original binary.

L8000:      CALL L04CC	; Clear the screen.
            CALL L801B	
            CALL L81BA	
L8009:      CALL L8217
L800C:      CALL L8324
            CALL L8504
            JR NC,L800C
L8014:      LD HL,L87FC
            INC (HL)
            JP L8009
The first call is pretty obvious, it simply clears the screen. Notice the original game assumed the VDP was already initialized, but we already took care of it with CALL setup_vdp.
The next call L801B apparently does graphics set up.

L801B:      LD HL,$0400	; VRAM bitmap data $80 character.
            LD DE,L806A
            LD BC,$00C8
            CALL L805D
            LD HL,$2400	; VRAM color data $80 character (1st).
            LD DE,L8112
            LD BC,$001B
            CALL L8148
            LD HL,$2C00	; VRAM color data $80 character (2nd).
            LD DE,L8112
            LD BC,$001B
            CALL L8148
            LD HL,$3400	; VRAM color data $80 character (3rd).
            LD DE,L8112
            LD BC,$001B
            CALL L8148
            LD HL,$3800	; VRAM sprite bitmaps.
            LD DE,L8404
            LD BC,$0100
            CALL L805D
            LD HL,$4400	; Obviously a patch.
            JP L83FB

L83FB:      CALL L0100
            LD HL,$41C2
            JP L0100
The target address for VRAM is in the register HL, while the source address is in DE, and the byte count is in BC. That's completely reversed from the standard Z80 definitions for LDIR, or the MSX LDIRVM BIOS subroutine.
As I was coding in machine code, any mistake was a pain to correct, especially if you needed to insert additional instructions! As you can see the jump to $83FB continues setting register 4 of VDP to zero, and then proceeds to set up register 1 of VDP for 16x16 sprites.
The VDP in high-resolution mode needs to have separate bitmap definitions for three 64-pixel-high areas for a total of 192 vertical rows. Setting the VDP register 4 is a trick for the VDP to repeat the top bitmap into the other two screen areas. I found this trick months ago experimenting different values for VDP registers.
So we mark L801B as "Setup graphics".
Then we have the L805D subroutine that simply copies data from the memory to VRAM.

L805D:      CALL L0100
L8060:      LD A,(DE)
            OUT (VDP),A
            INC DE
            DEC BC
            LD A,B
            OR C
            JR NZ,L8060
            RET
Now I can see why I did it that way as the L0100 subroutine uses HL as VDP address then it was easier for me to have the source data pointed by the register DE. I've replaced the original port $B0 (VDP write) and $c0 (VDP read) with the VDP definition for the current console (MSX or Colecovision).
It is followed by 200 bytes of bitmaps for the game:

L806A:      db $FF,$FF,$FF,$FF  ; $806A
            db $FF,$FF,$FF,$FF  ; $806E
            db $E7,$E7,$E7,$E7  ; $8072
            db $E7,$E7,$E7,$E7  ; $8076
            db $FF,$FF,$00,$FF  ; $807A
            db $FF,$00,$FF,$FF  ; $807E
            db $42,$42,$7E,$42  ; $8082
            db $42,$7E,$42,$42  ; $8086
            db $FE,$82,$BA,$AA  ; $808A
            db $BA,$82,$FE,$00  ; $808E
            db $BA,$BA,$BA,$BA  ; $8092
            db $BA,$BA,$BA,$BA  ; $8096
            db $EE,$00,$FF,$FF  ; $809A
            db $FF,$00,$00,$00  ; $809E
            db $42,$42,$7E,$42  ; $80A2
            db $42,$7E,$42,$42  ; $80A6
            db $EF,$EF,$EF,$00  ; $80AA
            db $FE,$FE,$FE,$00  ; $80AE
            db $7E,$7E,$7E,$00  ; $80B2
            db $6E,$6E,$6E,$00  ; $80B6
            db $00,$FF,$FF,$AA  ; $80BA
            db $44,$00,$00,$00  ; $80BE
            db $42,$42,$7E,$42  ; $80C2
            db $42,$7E,$42,$42  ; $80C6
            db $EE,$EE,$EE,$00  ; $80CA
            db $EE,$EE,$EE,$00  ; $80CE
            db $40,$30,$0C,$03  ; $80D2
            db $0C,$30,$40,$40  ; $80D6
            db $00,$FF,$00,$AA  ; $80DA
            db $55,$00,$FF,$00  ; $80DE
            db $81,$81,$C3,$BD  ; $80E2
            db $81,$81,$C3,$BD  ; $80E6
            db $81,$58,$37,$47  ; $80EA
            db $39,$27,$49,$27  ; $80EE
            db $47,$49,$27,$40  ; $80F2
            db $28,$15,$12,$27  ; $80F6
            db $00,$FE,$FE,$00  ; $80FA
            db $EF,$EF,$00,$00  ; $80FE
            db $0C,$0C,$18,$18  ; $8102
            db $30,$30,$18,$18  ; $8106
            db $54,$FE,$54,$FE  ; $810A
            db $54,$FE,$54,$00  ; $810E
This includes walls, columns, floor, and ladders (4 characters for each level), for a total of 5 levels, plus a kind of drain cover. Next is the color table for these bitmaps.

L8112:      db $08,$22,$08,$3C  ; $8112
            db $08,$A1,$08,$F1  ; $8116
            db $08,$74,$08,$E1  ; $811A
            db $01,$F1,$01,$11  ; $811E
            db $03,$E1,$03,$11  ; $8122
            db $08,$F1,$08,$6E  ; $8126
            db $08,$E1,$10,$F1  ; $812A
            db $08,$61,$08,$A1  ; $812E
            db $03,$F1,$02,$51  ; $8132
            db $03,$F1,$08,$E1  ; $8136
            db $08,$98,$08,$32  ; $813A
            db $01,$11,$06,$6E  ; $813E
            db $01,$11,$08,$31  ; $8142
            db $08,$F1  ; $8146
What is this? This data cannot be copied directly to the VDP, instead it looks like there are byte counts.

L8148:      CALL L0100
            LD B,C
L814C:      PUSH BC
            LD A,(DE)
            LD B,A
            INC DE
            LD A,(DE)
            INC DE
L8152:      OUT (VDP),A
            NOP
            DJNZ L8152
            POP BC
            DJNZ L814C
            RET
And that's right, the kid was smart enough to create a decompressor that reads a count of bytes and a byte to replicate. So 73 bytes replace 200 bytes of color.
Bitmaps used for the level backgrounds.
Bitmaps used for the level backgrounds along character number. Notice the order of wall, column, floor, and ladder.
Do you remember I mentioned "El Castillo Embrujado" from Input MSX? At age 11 I wasn't very confident in my graphical design abilities, so for my game I reused the sprite graphics for the player and the snakes. Many years later I discovered these graphics from "El Castillo Embrujado" were in fact a copy from another game, the famous Abu-Simbel Profanation for ZX Spectrum.
However, for this article I'll help my younger myself designing all-new graphics. If you are curious about it you can see the previous graphics set in the viboritas_orig.asm file.
Comparison of 1990 sprites versus updated sprites.
At the left you can see the 1990 sprites and at the right the updated sprites.
The new sprite set for Viboritas.
The new sprite set for Viboritas.

	;
	; Sprites for the player and half of the snakes.
	;
L8404:
	; $00 - Player going right (frame 1).
	DB $00,$01,$05,$03,$07,$03,$07,$1e
	DB $37,$67,$77,$74,$03,$0e,$0e,$0f
	DB $00,$50,$f0,$f0,$d0,$70,$10,$e0
	DB $00,$b8,$b8,$00,$c0,$f8,$7c,$00
	; $04 - Player going right (frame 2).
	DB $00,$02,$01,$03,$01,$03,$03,$07
	DB $07,$06,$06,$07,$03,$03,$03,$03
	DB $a8,$f8,$f8,$e8,$b8,$88,$70,$80
	DB $c0,$e0,$e0,$00,$c0,$00,$c0,$e0
	; $08 - Player going left (frame 1).
	DB $00,$0a,$0f,$0f,$0b,$0e,$08,$07
	DB $00,$1d,$1d,$00,$03,$07,$1e,$3e
	DB $00,$80,$a0,$c0,$e0,$c0,$e0,$78
	DB $ec,$e6,$ee,$2e,$c0,$70,$70,$f0
	; $0c - Player going right (frame 2).
	DB $15,$1f,$1f,$17,$1d,$11,$0e,$01
	DB $03,$07,$07,$00,$03,$00,$03,$07
	DB $00,$40,$80,$c0,$80,$c0,$c0,$e0
	DB $e0,$60,$60,$e0,$c0,$c0,$c0,$c0
	; $10 - Player using ladder (frame 1).
	DB $0a,$07,$0f,$0f,$07,$07,$03,$0c
	DB $1b,$70,$73,$02,$06,$06,$1e,$3e
	DB $a0,$c0,$e0,$e0,$ce,$ce,$98,$70
	DB $c0,$00,$c0,$60,$38,$3c,$00,$00
	; $14 - Player using ladder (frame 2).
	DB $05,$03,$07,$07,$73,$73,$19,$0e
	DB $03,$00,$03,$06,$1c,$3c,$00,$00
	DB $50,$e0,$f0,$f0,$e0,$e0,$c0,$30
	DB $d8,$0e,$ce,$40,$60,$60,$78,$7c
	; $18 - Snake going left (frame 1).
	DB $1b,$2d,$2d,$36,$1f,$7d,$9b,$03
	DB $0f,$1f,$3e,$3c,$3c,$3f,$1f,$0f
	DB $00,$00,$00,$00,$00,$80,$80,$82
	DB $02,$06,$06,$0e,$cc,$ec,$fc,$38
	; $1c - Snake going right (frame 2).
	DB $00,$0d,$16,$16,$1b,$0f,$1e,$5d
	DB $61,$0f,$1f,$1e,$1e,$1f,$0f,$07
	DB $00,$80,$80,$80,$00,$80,$c0,$c0
	DB $c0,$84,$0c,$cc,$d8,$f8,$b8,$30

Music player

At this moment of the analysis, the following routine isn't called yet.

L815B:      LD HL,L87FA
            INC (HL)
            LD A,(HL)
            CP $08
            JR NZ,L8194
            LD (HL),$00
            DEC HL
            INC (HL)
            LD A,(HL)
            CP $30
            JR NZ,L816F
            LD (HL),$01
L816F:      LD A,(HL)
            ADD A,255 AND (L8744-1)
            LD L,A
            LD H,(L8744-1)>>8
            CALL L8197
            NOP
            LD A,(HL)
            OUT ($80),A
            INC HL
            LD A,$01
            OUT ($00),A
            LD A,(HL)
            OUT ($80),A
            LD A,$07
            OUT ($00),A
            LD A,$B8
            OUT ($80),A
            LD A,$08
            OUT ($00),A
            LD A,$0A
            OUT ($80),A
L8194:      JP L8398

L8197:      LD A,(HL)
            ADD A,A
            ADD A,255 AND (L81A2-2)
            LD L,A
            LD H,(L81A2-2)>>8
            XOR A
            OUT ($00),A
            RET

L81A2:      dw $01ac
	    dw $0153
	    dw $011d
	    dw $00fe
	    dw $00f0
	    dw $0140
	    dw $00d6
	    dw $00be
	    dw $00b4
	    dw $00aa
	    dw $00a0
	    dw $00e2

L8744:      db $01,$02,$03,$04  ; $8744
            db $05,$04,$03,$02  ; $8748
            db $01,$02,$03,$04  ; $874C
            db $05,$04,$03,$02  ; $8750
            db $06,$04,$07,$08  ; $8754
            db $09,$08,$07,$04  ; $8758
            db $06,$04,$07,$08  ; $875C
            db $09,$08,$07,$04  ; $8760
            db $03,$0C,$08,$0A  ; $8764
            db $0B,$0A,$08,$0C  ; $8768
            db $06,$04,$07,$08  ; $876C
            db $09,$08,$07,$04  ; $8770
Ok, it increments a byte at L87FA, and when it reaches the value 8 it is reset to zero and proceeds to increment L87F9 until it reaches 48 when it is reset to 1. Of course! L87F9 is the index number in the song table, and L87FA is the counter of note duration.
Then it uses the index to get the note to play from L8744. Here is a machine code trick that isn't useful when converting to assembler mnemonics: You know the data is fixed at the address, so there is no handling for carry to the higher address byte.
Now we have another patch, this time calling L8197 to get the note frequency to play, and then it writes to the AY-3-8910 sound chip. The $00 port address sets the AY-3-8910 index register, and the $80 port address sets the AY-3-8910 data register. It even sets the register 7 of PSG to $38 to disable white noise, and this value can burn for real some MSX1 computers. Let us replace the sound code:

            CALL L8197
	if COLECO
	    LD A,(HL)
	    INC HL
	    LD H,(HL)
	    LD L,A
	    AND $0F
	    OR $80
	    OUT (PSG),A
	    SRL H
	    RR L
	    SRL H
	    RR L
	    SRL H
	    RR L
	    SRL H
	    RR L
	    LD A,L
	    OUT (PSG),A
	    LD A,$93
	    OUT (PSG),A
	else
	    LD E,(HL)
	    LD A,0
	    CALL WRTPSG
	    INC HL
	    LD E,(HL)
	    LD A,1
	    CALL WRTPSG
	    LD E,$0A
	    LD A,$08
	    CALL WRTPSG
	endif
L8194:      JP L8398

L8197:      LD A,(HL)
            ADD A,A
            ADD A,255 AND (L81A2-2)
            LD L,A
            LD H,(L81A2-2)>>8
            RET
Also at first glance, I thought this routine was written first, but then I realized it occupies the space of an uncompressed color table! When I optimized the color table definition to use compression, I added the song player in the freed space!
This means the first version of my game didn't have any music, and there's a chance that somewhere in my files exists a printout. And I just remembered a thing: I coded the game without music, and a student had a background in music, and he handed me some musical notes that I implemented terribly because I didn't know anything about music timing.
The music is a rendition of a boogie-woogie. The music player still goes on, and there is a very weird patch jumping at L8398. But we'll see it later, as it looks like the keyboard code.

Initialization

Now we go to the next unexplored code at L81BA:

L81BA:      XOR A
            LD (L87F3),A
            LD (L87F4),A
            LD (L87F7),A
            LD (L87F8),A
            LD A,$F0
            LD (L87F5),A
            LD A,$01
            LD (L87F6),A
            LD A,$0F
            LD (L8786),A
            LD A,$00
            LD (L8787),A
            LD HL,$0000
            LD (L87F9),HL
            LD A,$02
            LD (L87FB),A
            CALL L04CC
            LD HL,$3EE9
            CALL L0100
            CALL L0169
            db "(C) OTEK 1990",0
            LD HL,$3EAC
            CALL L0100
            CALL L0169
            db "VIDAS:0",0
            LD A,$01
            JP L82A5
This is looking like an initialization code (let us add a note to L81BA as game initialization).
We'll discover the function of each variable soon. So far it cleans again the screen, sets up the VDP to the last row of the screen, and shows the copyright message. OTEK comes from my father's initials (Oscar Toledo Esteva) which we used as a kind of company name.
Also, it shows the number of remaining lives (VIDAS in Spanish), and... another patch jumps to L82A5.

L82A5:      LD (L87FC),A
            XOR A
            LD (L87FE),A
            LD (L87FF),A
            RET
It is simply some more variable initialization.

Screen drawing

Now another routine L8217 that is called immediately after in L8009:

L8217:      LD A,(L87FC)
            ADD A,A
            ADD A,A
            ADD A,$7C
            LD (L87FD),A
            LD HL,$3C00
            CALL L0100
            LD B,$A0
L8229:      PUSH BC
            LD B,$03
L822C:      LD A,(L87FD)
            OUT (VDP),A
            INC HL
            DJNZ L822C
            LD A,(L87FD)
            INC A
            OUT (VDP),A
            INC HL
            POP BC
            DJNZ L8229
            LD HL,$3C80
            LD B,$04
L8243:      PUSH BC
            PUSH HL
            CALL L0100
            LD B,$20
L824A:      LD A,(L87FD)
            ADD A,$02
            OUT (VDP),A
            INC HL
            DJNZ L824A
            POP HL
            LD BC,$00A0
            ADD HL,BC
            POP BC
            DJNZ L8243
            LD HL,$4701
            CALL L0100
            LD HL,$2000
            CALL L8277
            LD HL,$2800
            CALL L8277
            LD HL,$3000
            CALL L8277
            JP L8288
It starts by getting a variable from L87FC, multiplying by 4, adding $7c, and saving the result at L87FD. L87FC is initialized to one. This starts at $80, it sounds like the character number for level definition. It draws in sequence 160 walls (3 characters) + columns (one character), then it draws over 4 floors starting at row 4 ($3c80), each one 32 characters wide, using the character in L87FD offset by 2.
It sets the border to black ($4701), and then the base charset ($00-$7f characters) for the three zones of the screen is set to black (three calls to L8277)

L8277:      LD A,H
            ADD A,$04
            LD B,A
            CALL L0100
L827E:      LD A,$F1
            OUT (VDP),A
            INC HL
            LD A,H
            CP B
            JR NZ,L827E
            RET

L8288:      LD HL,$3E5E
            CALL L0100
            LD A,$94
            OUT (VDP),A
            LD HL,$3C80
            CALL L82B0
            LD HL,$3D20
            CALL L82B0
            LD HL,$3DC0
            CALL L82B0
            RET
The L8288 patch adds the "drain" character $94 at the bottom right of the screen. I still don't understand why I didn't just draw a 2x2 door, but probably I felt like there were space constraints (defining the graphics and drawing the tiles).
At the end, it calls 3 times the L82B0 subroutine with different screen rows as the base:

L82B0:      LD A,(L87FC)
            LD B,A
            LD A,$06
            SUB B
            LD B,A
L82B8:      PUSH BC
            PUSH HL
            NOP
            LD D,$00
            NOP
            CALL L82CB
            LD E,A
            ADD HL,DE
            CALL L830F
            POP HL
            POP BC
            DJNZ L82B8
            RET
This L82B0 subroutine subtracts the level number from 6 and calls a subroutine L82CB to get an offset, and then L830F to do something.

L82CB:      PUSH BC
            PUSH DE
            PUSH HL
            LD HL,(L8780)
            LD DE,(L8782)
            LD BC,(L8784)
            ADD HL,HL
            ADD HL,HL
            ADD HL,BC
            ADD HL,DE
            LD (L8780),HL
            ADD HL,DE
            ADD HL,DE
            ADD HL,BC
            ADD HL,BC
            ADD HL,BC
            ADD HL,HL
            ADD HL,HL
            ADD HL,HL
            ADD HL,HL
            ADD HL,DE
            ADD HL,BC
            LD (L8782),HL
            ADD HL,DE
            ADD HL,DE
            ADD HL,BC
            ADD HL,HL
            ADD HL,DE
            ADD HL,BC
            ADD HL,BC
            ADD HL,BC
            ADD HL,BC
            LD (L8784),HL
            LD HL,(L8780)
            LD DE,(L8782)
            LD BC,(L8784)
            ADD HL,DE
            ADD HL,BC
            LD A,H
            ADD A,L
            AND $1F
            POP HL
            POP DE
            POP BC
            RET
It happens L82CB looks a lot like a random number generator, and only gets a number between 0 and 31 in the accumulator register.

L830F:      LD B,$05
            LD A,(L87FD)
            ADD A,$03
L8316:      PUSH AF
            CALL L0100
            POP AF
            OUT (VDP),A
            LD DE,$0020
            ADD HL,DE
            DJNZ L8316
            RET
¡Mystery solved! L830F draws a ladder on the screen. Each ladder is 5 rows high, and it is drawn using the level base character offset by 3. In the first level it will draw 5 ladders on each floor, while in the fifth level, it will draw only one ladder for each floor. That's an attempt to make more difficult levels.
With all this code analyzed we can mark safely L8217 as the level drawing code.

The hero and the foes

Now we have the first routine called from the main loop and it is L8324:

L8324:      LD HL,$1B00
            LD A,(L8786)
            CALL L8390
            INC HL
            LD A,(L8787)
            CALL L8390
            INC HL
            LD A,(L87FE)
            CALL L8390
            INC HL
            LD A,$0F
            CALL L8390
            INC HL
            LD A,$38
            CALL L8390
            INC HL
            LD DE,L87F3
            CALL L86C5
            LD A,$0E
            CALL L8390
            INC HL
            LD A,$60
            CALL L8390
            INC HL
            LD DE,L87F5
            CALL L86C5
            LD A,$0E
            CALL L8390
            INC HL
            LD A,$88
            CALL L8390
            INC HL
            LD DE,L87F7
            CALL L86C5
            LD A,$0E
            CALL L8390
            JP L815B

L8390:      PUSH AF
            CALL L0100
            POP AF
            OUT (VDP),A
            RET
It loads HL with $1b00, pointing to the Sprite Attribute Table. The VRAM place where sprites are positioned on the screen. And it starts reading variables and writing to VRAM using L8390 (pretty similar to WRTVRM of MSX)
L8786 is the Y-coordinate for the player, L8787 is the X-coordinate for the player, L87FE is the sprite frame for the player. The player color is white.
It is easily deduced next that the enemies are placed at fixed vertical positions on the screen ($38, $60, and $88) using a generic routine L86C5. Notice also that it chain links to the L815B subroutine for playing the background music, which in turn chain links to the keyboard decode subroutine (L8398).

L86C5:      LD A,(DE)
            CALL L8390
            INC DE
            INC HL
            LD A,(DE)
            LD B,$18
            CP $00
            JR NZ,L86D4
            LD B,$20
L86D4:      LD A,(L8788)
            XOR $01
            LD (L8788),A
            BIT 0,A
            LD A,$00
            JR Z,L86E4
            LD A,$04
L86E4:      ADD A,B
            CALL L8390
            INC HL
            PUSH HL
            LD HL,$390C
            LD DE,L8704
            LD BC,$0034
            CALL L805D
            POP HL
            RET
The first byte pointed by DE is used for the X-coordinate of the enemy. And the next byte signals the movement direction to select the sprite frame for the enemy. It also switches frames using L8788 to get alternate movement frames (along with B set to base frame $18 or $20). Then it does something really weird, copying the memory area L8704 into VRAM address $390c. Oh, I see, it defines two sprites very late in the game (the two sprite frames for snakes moving to the right), it is kind of obvious that I didn't foresee all the required sprites for the game.
For this updated version of the game, I'll modify slightly the code:

            LD HL,$3900	; Define frame sprites $20 and $24
            LD DE,L8700	; Data for snake going to right.
            LD BC,$0040	; Length of data.
            CALL L805D	; Copy to VRAM.
It would not have fit by 8 bytes, or I would have to move a significant portion of code to make space. In this case my option could have been moving the portion of code at $8504-$8533 (the complex enemy movement code), but I didn't have a MOVE command in the monitor program. I had to copy manually the machine code at the new position.

	;
	; Extra sprites for snakes going right.
	;
L8700:
	DB $00,$01,$01,$01,$00,$01,$03,$03
	DB $03,$21,$30,$33,$1b,$1f,$1d,$0c
	DB $00,$b0,$68,$68,$d8,$f0,$78,$ba
	DB $86,$f0,$f8,$78,$78,$f8,$f0,$e0

	DB $00,$00,$00,$00,$00,$01,$01,$41
	DB $40,$60,$60,$70,$33,$37,$3f,$1c
	DB $d8,$b4,$b4,$6c,$f8,$be,$d9,$c0
	DB $f0,$f8,$7c,$3c,$3c,$fc,$f8,$f0

Player movement

The music player chain links to the keyboard code:

L8398:      CALL L0447
            CP $10
            JP Z,L83DD
            CP $0F
            JP Z,L83B5
            CP $37
            JP Z,L85B5
            CP $38
            JP Z,L8567
            CP $02
            JP Z,L8684
            RET
Now this code is looking every moment more like spaghetti code, and it also needs to be rewritten for portable joystick handling:

L8398:      CALL GTSTCK
            CP $07		; Going left?
            JP Z,L83DD
            CP $03		; Going right?
            JP Z,L83B5
            CP $01		; Going up?
            JP Z,L85B5
            CP $05		; Going down?
            JP Z,L8567
	    CALL GTTRIG
            CP $ff		; Button pressed?
            JP Z,L8684
            RET
The first joystick subroutine is L83B5:

L83B5:      LD HL,L8787
            INC (HL)
            INC (HL)
            NOP
            LD A,(HL)
            CP $00
            JR NZ,L83C2
            LD (HL),$FE
L83C2:      LD A,(L87FE)
            CP $04
            JR NZ,L83CD
            LD A,$00
            JR L83CF

L83CD:      LD A,$04
L83CF:      LD (L87FE),A
            RET
At this point, we know that L8787 is the X-coordinate of the player (based on the Sprite Attribute Table writes), and the double increment makes clear that the player moves to the right. If the X-coordinate becomes 0, it is rewritten with limit $fe (254 pixels). It also animates the player switching between sprite frames $00 and $04.

L83DD:      LD HL,L8787
            DEC (HL)
            DEC (HL)
            NOP
            LD A,(HL)
            CP $FE
            JR NZ,L83EA
            LD (HL),$00
L83EA:      LD A,(L87FE)
            CP $0C
            JR NZ,L83F5
            LD A,$08
            JR L83F7

L83F5:      LD A,$0C
L83F7:      LD (L87FE),A
            RET
The next subroutine is the opposite: Moving the player to the left by two pixels. It also checks for exceeding the left border and sets the X-coordinate to zero. It animates the player switching between sprite frames $08 and $0c.
The NOP instruction after the two decrements makes me think that I considered moving horizontally the player at a speed of three pixels.

Using ladders

The code to allow the player to go up and down over the ladders is heavily patched, so probably it took me a lot of effort and experiments.
Let us start with the code to go down (this was coded first because the player needs to go down from the top floor):

	;
	; Move the player downward.
	;
L8567:      LD HL,$1B00
            CALL L85A0
            CALL L85AE
            NOP
            LD D,A
            INC HL
            CALL L85A0
            CALL L85FF
            RRCA
            RRCA
            LD E,A
            LD A,D
            LD L,A
            LD H,$00
            ADD HL,HL
            ADD HL,HL
            ADD HL,HL
            ADD HL,HL
            ADD HL,HL
            LD D,$00
            ADD HL,DE
            LD DE,$3C40
            ADD HL,DE
            CALL L85A0
            LD B,A
            LD A,(L87FD)
            ADD A,$03
            CP B
            RET NZ
            CALL L85E9
            ADD A,$02
L859C:      LD (L8786),A
            RET

L85A0:      LD A,L
            OUT (VDP+1),A
            LD A,H
            OUT (VDP+1),A
            NOP
            NOP
            NOP
            NOP
            NOP
            IN A,(VDP)
            RET

L85AE:      INC A
            AND $F8
            RRCA
            RRCA
            RRCA
            RET

L85E9:      LD D,$00
            ADD HL,DE
            LD A,(L87FE)
            LD B,$14
            CP $10
            JR Z,L85F7
            LD B,$10
L85F7:      LD A,B
            LD (L87FE),A
            LD A,(L8786)
            RET

L85FF:      ADD A,$04
            AND $F8
            RRCA
            RET

L8605:      ADD A,$03
            CP B
            RET Z
            POP HL
            LD A,(L8786)
            INC A
            AND $F8
            JP L8631

L8631:      DEC A
            NOP
            LD (L8786),A
            RET
The innocent kid reads from VRAM the coordinates of the player, but why on Earth? These variables were already available in RAM.
It first reads from VRAM $1b00 the Y-coordinate of the player into register D converted to a screen row coordinate, and it also reads the X-coordinate into register E and adjusts it to a screen column coordinate. It finally takes both numbers to create a pointer to the VRAM screen.
	D = (Y + 1) / 8
	E = (X + 4) / 8
	HL = D * 32 + E + $3c20
You can see I did LD A,D followed by LD L,A when I could simply do LD L,D.
It reads the character from VRAM (CALL L85A0), and it checks if the character is a ladder (the contents of L87FD plus 3). It calls a patch L85E9 that for some reason adds a value to the content of HL, animates the player using the ladder (sprite frames $10 and $14), and gets the Y-coordinate of the player to move it two pixels downward.

	;
	; Move the player upward.
	;
L85B5:      LD A,(L8786)
            CALL L85AE
            LD D,A
            INC HL
            LD A,(L8787)
            CALL L85FF
            RRCA
            RRCA
            LD E,A
            LD A,D
            LD L,A
            LD H,$00
            ADD HL,HL
            ADD HL,HL
            ADD HL,HL
            ADD HL,HL
            ADD HL,HL
            LD D,$00
            ADD HL,DE
            LD DE,$3C20
            ADD HL,DE
            CALL L85A0
            LD B,A
            LD A,(L87FD)
            CALL L8605
            NOP
            CALL L85E9
            SUB $02
            JP L859C
The code for moving the player upwards is pretty similar, and somehow I did the right thing in this code using the existing coordinates in RAM. This means I was reaching my limits, and having 2K of machine code in the head isn't so easy!
There are a few differences more like the different offset on the screen ($3c20 versus $3c40), and the fact it calls L8605 to do a comparison with the ladder character. If it isn't a ladder, it aligns the player vertically (again using a patch), and using POP HL it returns to the main loop instead of the original caller. If it is a ladder, it moves the player two pixels upwards.
Now for the great embarrassing moment: the player can walk over the air. Because the code for handling left and right never checks if the player is over a floor. As the floors are always in the same vertical position, it would be simply a matter of checking if the player is over one of the valid Y-coordinates, but I can remember vaguely I was afraid of moving the code again. Lazy kid!

Winning the game

Once the player reaches the grid in the bottom-right of the screen, the fire button should be pressed to pass the level. I watched in delight as students forgot to press the button and they were caught by the snake.

	;
	; Button press to exit level.
	; 
L8684:      LD A,(L8786)
            CP $87
            RET NZ
            LD A,(L8787)
            CP $E8
            RET C
            CP $F8
            RET NC
            LD SP,L87F0
            LD A,$0F
            LD (L8786),A
            XOR A
            LD (L8787),A
            LD A,(L87FC)
            CP $05
            JP NZ,L8014
            LD HL,$3D4A
            CALL L0100
            CALL L0169
            db "HAS GANADO !",0
            LD A,$08
            OUT ($00),A
            XOR A
            JP L87B4

L87B4:      OUT ($80),A
            JP L878A

L878A:      LD B,$05	; Big delay.
L878C:      PUSH BC
            LD BC,$0000
L8790:      DEC BC
            LD A,B
            OR C
            JR NZ,L8790
            POP BC
            DJNZ L878C
            LD SP,L87F0	; Reset Stack Pointer.
            LD A,$0F	; Reset Y-coordinate for the player.
            LD (L8786),A
            XOR A		; Reset X-coordinate for the player.
            LD (L8787),A
            LD A,$01	; Restart at level 1.
            LD (L87FC),A
            LD HL,L87F9
            LD (HL),$00
            INC HL
            LD (HL),$00
            JP L8009
The subroutine first checks for the Y-coordinate to be $87, and the X-coordinate is between $e8 and $f7 (good tolerance) and if the conditions are met it resets the stack pointer, sets the player again at the top-left of the screen, and if the level number isn't 5 then it jumps to L8014 to increase the level number else it shows a message "HAS GANADO" (Spanish for you win) on the screen.
It also turns off the music in another tender example of chain linking because of the heavily patched code.
The sound code should be rewritten as this:

            db "HAS GANADO !",0
	if COLECO
	    ld a,$9f
	    out (PSG),a
	else
	    ld e,$00
	    ld a,$08
	    call WRTPSG
	endif
            JP L87B4

L87B4:      	
            JP L878A
The L878A routine does a big delay so the "HAS GANADO !" message stays on the screen, and then resets the game, and sends the player back to level 1.

Enemy movement

The second subroutine called by the main loop of the game is L8504, it shows heavy patches.

L8504:      CALL L850A
            JP L83D3
It calls L850A and then L83D3. L83D3 is more akin to a loop to make the game run slower (I still didn't know the VDP interrupt line, nor did I have the line connected to the Z80 processor). After setting BC to $1000, it also updates the current number of lives on the screen.

L83D3:      CALL L861E
L83D6:      DEC BC
            LD A,B
            OR C
            JR NZ,L83D6
            AND A
            RET

L861E:      LD BC,$1000
            LD A,(L87FB)
            ADD A,$30
            LD HL,$3EB2
            PUSH AF
            CALL L0100
            POP AF
            OUT (VDP),A
            RET
The subroutine L850A is longer:

L850A:      LD HL,L87F3
            CALL L8517
            LD L,255 AND L87F5
            CALL L8517
            LD L,255 AND L87F7
L8517:      INC HL
            LD A,(HL)
            OR A
            LD B,$03
            JR Z,L8520
            LD B,$FD
L8520:      DEC HL
            LD A,(HL)
            ADD A,B
            LD (HL),A
            CP $FF
            JR NZ,L852D
            INC HL
            LD (HL),$01
            JR L8533

L852D:      OR A
            JR NZ,L8533
            INC HL
            LD (HL),$00
L8533:      CALL L855B
            CP B
            RET C
            CP C
            RET NC
            LD A,L
            SUB 255 AND L87F3
            RRCA
            ADD A,A
            ADD A,A
            ADD A,$04
            LD L,A
            LD H,$1B
            LD A,L
            OUT (VDP+1),A
            LD A,H
            OUT (VDP+1),A
            NOP
            NOP
            NOP
            NOP
            IN A,(VDP)
            LD B,A
            LD A,(L8786)
            INC A
            CP B
            RET NZ
            JP L8613

L855B:      DEC HL
            LD A,L
            AND $FE
            OR $01
            LD L,A
            LD B,(HL)
            JP L8738

L8738:      LD A,(L8787)
            LD C,B
            DEC B
            DEC B
            DEC B
            INC C
            INC C
            INC C
            INC C
            RET
It uses L8517 each time with a pointer to one of the enemies (L87F3, L87F5, and L87F7). For each enemy, it checks the current direction and selects an X-displacement (-3 or +3 pixels) in the B register. If it reaches a certain coordinate it switches the movement direction.
Once this has been done, another patch calls to L855B to make HL point exactly to the X-coordinate of the enemy (this code is dependent on the memory address of the enemy coordinates). It reads the current X-coordinate into the B register and jumps to another patch in L8738, where it reads the X-coordinate of the player in A, makes a copy of B in C, subtracting 3 from B, and adds 4 to C.
When it has created a collision width (minimum is B, maximum is C) it does a comparison of A (player X-coordinate) with B and returns if it is less than, and a comparison against C and returns if it is equal or greater than.
As the enemy state doesn't contain its Y-coordinate, it determines the sprite from the enemy data address, reads the Sprite Attribute Table from VRAM to get the Y-coordinate and does a comparison with the player Y-coordinate (L8786), and returns if both aren't equal, else it jumps to L8613 to kill the player.
There is a bug in this code and the player can die accidentally while walking. In an amazing example of how bugs can perdure for years, I couldn't find this accidental kill bug for years until today (Feb/06/2024) I finally used debuging tools of BlueMSX. It is pretty easy once found, when a snake is aligned with the player it returns correctly because the player isn't in the same floor as the snake, but it loses the value of the register HL because the VRAM read, and the next snake X-coordinate will be read from ROM creating a fixed invisible snake in the next floor. It will fail randomly in a position dependant of the platform. Do you want to correct it? Just replace my "smart" optimization in L850A to load each time the full value of HL with the address of the enemy data instead of only the L register. Case closed, it only took me 34 years.
Let's continue:

L8613:      CALL L837A
            DEC (HL)
            SCF
            LD SP,L87F0
            JP L8637

L837A:      XOR A
            OUT ($00),A
            LD A,$AE
            OUT ($80),A
            LD A,$01
            OUT ($00),A
            LD A,$06
            OUT ($80),A
            JP L8774

L8774:      LD BC,$0000
L8777:      DEC BC
            LD A,B
            OR C
            JR NZ,L8777
            JP L866F

L866F:      LD A,$08
            OUT ($00),A
            XOR A
            OUT ($80),A
            LD BC,$0000
L8679:      DEC BC
            LD A,B
            OR C
            JR NZ,L8679
            LD HL,L87FB
            JR L86F8

L86F8:      XOR A
            LD (L87F9),A
	    LD (L87FA),A
            RET

L8637:      LD A,$0F
            LD (L8786),A
            XOR A
            LD (L8787),A
            LD A,(L87FB)
            CP $FF
            JP NZ,L8009
            LD HL,$3D4A
            CALL L0100
            CALL L0169
            db "FIN DE JUEGO",0
            LD B,$05
L8660:      PUSH BC
            LD BC,$0000
L8664:      DEC BC
            LD A,B
            OR C
            JR NZ,L8664
            POP BC
            DJNZ L8660
            JP L8000
It is pretty embarrassing this chain-linking of code, but let us go in parts.
The first line of code at L8613 calls L837A, the ultimate purpose is loading HL with L87FB to point to the number of lives of the player and decrement it.
But L837A also creates a sound effect (a first!) then jumps to L8774 for a small delay, and then jumps to L866F to turn off the volume, does another delay, loads HL with a pointer to the number of lives, and resets the music player's variables.
After it decrements the number of lives, it sets the carry flag but obviously, I got lost in this path because it is never used. The stack pointer is reset, the player is set again to the start point in L8637, and if there are still lives it jumps to L8009 to continue the game, or else it displays a message "FIN DE JUEGO" (game over in Spanish), it waits a longer time, and it resets completely the game jumping to L8000.
We need to patch the L837A and L866F sound routines with this:

L837A:
	if COLECO
	    ld a,$8E
	    out (PSG),a
	    ld a,$2a
	    out (PSG),a
	else
	    ld e,$ae
	    ld a,$00
	    call WRTPSG
	    ld e,$06
	    ld a,$01
	    call WRTPSG
	endif
            JP L8774

L866F:
	if COLECO
	    ld a,$9f
	    out (PSG),a
	else
	    ld e,$00
	    ld a,$08
	    call WRTPSG
	endif
            LD BC,$0000
L8679:      DEC BC

The used variables

The final list of variables inside the code are:

L8780:      rb 2	; Random generator 1.
L8782:      rb 2	; Random generator 2.
L8784:      rb 2	; Random generator 3.
L8786:      rb 1	; Y-coordinate for the player.
L8787:      rb 1	; X-coordinate for the player.
L8788:      rb 1	; Animation bit for snakes.

L87F3:      rb 1	; X-coordinate of enemy 1.
L87F4:      rb 1	; X-direction of enemy 1.
L87F5:      rb 1	; X-coordinate of enemy 2.
L87F6:      rb 1	; X-direction of enemy 2.
L87F7:      rb 1	; X-coordinate of enemy 3.
L87F8:      rb 1	; X-direction of enemy 3.
L87F9:      rb 1	; Note index for music player.
L87FA:      rb 1	; Tick counter for music player.
L87FB:      rb 1	; Current lives.
L87FC:      rb 1	; Current level. 
L87FD:      rb 1	; Base character for drawing levels.
L87FE:      rb 1	; Sprite frame for the player.
L87FF:      rb 1	; Not used, yet initialized.
The stack pointer used to be at $87F0 for 2K RAM student computers in 1990. Later moved to $fff0 for 32K RAM (1992).
You can download the ROM for the game ready to be played on a Colecovision or MSX. I've also included the commented source code. The only difference between this and my 1990 game is the redesigned graphics and adjustments to level colors to enhance visibility. The original colors blended badly on modern emulators (in 1990 I could adjust contrast in the Sony Trinitron TV).
The code can be assembled using tniASM v0.44.

Epilogue

A lot of bytes could be saved in this game by refactoring some parts like using an extra byte to preserve the vertical position of enemies, moving some initialization code out of the main loop (lives update and snake sprite definition), using data available on RAM instead of reading VRAM, and compacting the music player code.
On the other side, it reflects my abilities at the time. I could have almost 2K of machine code on my head, there wasn't a plan ahead (denoted by the ton of patches). I was still learning how to code a platform game, and I wasn't too able to draw graphics.
Writing games or other code directly in machine code isn't practical. Although at first glance you can have everything on your head, you'll forget completely after a few years, and also unless you have some paper documentation there aren't any helpful comments!
I would have used an assembler program if these were readily available, but I had none until I wrote mine some years after. The software stores in Mexico were scarce, also I never could find something so esoteric as a Z80 assembler program when the IBM PC was already the dominant machine.
However, my objective of developing a game in 2K RAM was met. Students were surprised a real game could work on their computer. I think I distributed a few copies as printed sheets with the binary and another few copies in floppies.
I learned as I developed the game, and I didn't make again the mistake of allowing the player to walk into the void. But still for many years, I kept coding in machine code and doing spaghetti code when I needed to insert code, but that is a history for another day.

Addendum

I was sure there was a printout of the game, but it wasn't in my documents. Somehow my father got my folder in his archive, and I was very happy to take pictures of the sheets. The game was printed in a dot-matrix printer using continuous paper (you can see the cuts in the picture).
Viboritas machine code printout, page 1 Viboritas machine code printout, page 2 Viboritas machine code printout, page 3
I did a comparison of the machine code against the binary I got from the floppy disk, and this is a previous version! There is a single byte of graphics that is different, it starts with 4 lives (instead of 2) and the VDP port addresses are different (data is $01 instead of $b0 and $c0, and address was $02). The code to restart the game when the player wins is completely missing, and instead it simply turns off the sound and halts the processor.
You can see some indications with my child's writing to personalize the gameplay, like music speed, number of lives, and game speed. I've covered the name of the student who provided me the notes for the music, as I don't have a way to contact him to ask for permission to show his name, the other name shown is the author of El Castillo Embrujado because of the sprites for the player and the snakes (now I know these sprites come from Abu-Simbel Profanation for ZX Spectrum).
I added the binary and its disassembly to the viboritas.zip file.

Extras

In March 10, 2024, I was searching for more programs written in my early years, and I found this printout behind some notes. It was typical for us to recycle paper using the blank back. The surprising thing here is the original name for the game, do you remember I liked the name Future Knight? I used "El Guerrero del Futuro" (Future Warrior) as the initial title for the game.
Viboritas machine code early printout, page 1
Furthermore, I was awesome to discover this is the version with the uncompressed color table! The addresses $8112 to $81b9 contain the color table ready to copy to VRAM so this version is missing the music player. Also, the random number generator variables are located at $8700-$8705.
Sadly, I only found the first page of the printout so it isn't enough to reconstruct the binary because of the displaced variables, and therefore not added to the zip file.

Related links

Last modified: Mar/10/2024