Add system-specific boot symbols and CPU instruction tests
Introduced symbol files for various Game Boy systems (CGB, AGB, MGB, SGB) to define boot sequences and functionalities. Included CPU instruction behavior tests, with detailed coverage of standard operations and interrupt handling. Added documentation for test execution and internal framework operations.
This commit is contained in:
78
cpu_instrs/source/01-special.s
Normal file
78
cpu_instrs/source/01-special.s
Normal file
@@ -0,0 +1,78 @@
|
||||
; Tests instructions that don't fit template
|
||||
|
||||
.include "shell.inc"
|
||||
|
||||
main:
|
||||
set_test 2,"JR negative"
|
||||
ld a,0
|
||||
jp jr_neg
|
||||
inc a
|
||||
- inc a
|
||||
inc a
|
||||
cp 2
|
||||
jp nz,test_failed
|
||||
jp +
|
||||
jr_neg:
|
||||
jr -
|
||||
+
|
||||
|
||||
set_test 3,"JR positive"
|
||||
ld a,0
|
||||
jr +
|
||||
inc a
|
||||
+ inc a
|
||||
inc a
|
||||
cp 2
|
||||
jp nz,test_failed
|
||||
|
||||
|
||||
set_test 4,"LD PC,HL"
|
||||
ld hl,+
|
||||
ld a,0
|
||||
ld pc,hl
|
||||
inc a
|
||||
+ inc a
|
||||
inc a
|
||||
cp 2
|
||||
jp nz,test_failed
|
||||
|
||||
|
||||
set_test 5,"POP AF"
|
||||
ld bc,$1200
|
||||
- push bc
|
||||
pop af
|
||||
push af
|
||||
pop de
|
||||
ld a,c
|
||||
and $F0
|
||||
cp e
|
||||
jp nz,test_failed
|
||||
inc b
|
||||
inc c
|
||||
jr nz,-
|
||||
|
||||
|
||||
set_test 6,"DAA"
|
||||
; Test all combinations of A and flags (256*16 total)
|
||||
ld de,0
|
||||
- push de
|
||||
pop af
|
||||
daa
|
||||
|
||||
push af
|
||||
call update_crc
|
||||
pop hl
|
||||
ld a,l
|
||||
call update_crc
|
||||
|
||||
inc d
|
||||
jr nz,-
|
||||
|
||||
ld a,e
|
||||
add $10
|
||||
ld e,a
|
||||
jr nz,-
|
||||
|
||||
check_crc $6A9F8D8A
|
||||
|
||||
jp tests_passed
|
||||
73
cpu_instrs/source/02-interrupts.s
Normal file
73
cpu_instrs/source/02-interrupts.s
Normal file
@@ -0,0 +1,73 @@
|
||||
; Tests DI, EI, and HALT (STOP proved untestable)
|
||||
|
||||
.include "shell.inc"
|
||||
|
||||
main:
|
||||
wreg IE,$04
|
||||
|
||||
set_test 2,"EI"
|
||||
ei
|
||||
ld bc,0
|
||||
push bc
|
||||
pop bc
|
||||
inc b
|
||||
wreg IF,$04
|
||||
interrupt_addr:
|
||||
dec b
|
||||
jp nz,test_failed
|
||||
ld hl,sp-2
|
||||
ldi a,(hl)
|
||||
cp <interrupt_addr
|
||||
jp nz,test_failed
|
||||
ld a,(hl)
|
||||
cp >interrupt_addr
|
||||
jp nz,test_failed
|
||||
lda IF
|
||||
and $04
|
||||
jp nz,test_failed
|
||||
|
||||
set_test 3,"DI"
|
||||
di
|
||||
ld bc,0
|
||||
push bc
|
||||
pop bc
|
||||
wreg IF,$04
|
||||
ld hl,sp-2
|
||||
ldi a,(hl)
|
||||
or (hl)
|
||||
jp nz,test_failed
|
||||
lda IF
|
||||
and $04
|
||||
jp z,test_failed
|
||||
|
||||
set_test 4,"Timer doesn't work"
|
||||
wreg TAC,$05
|
||||
wreg TIMA,0
|
||||
wreg IF,0
|
||||
delay 500
|
||||
lda IF
|
||||
delay 500
|
||||
and $04
|
||||
jp nz,test_failed
|
||||
delay 500
|
||||
lda IF
|
||||
and $04
|
||||
jp z,test_failed
|
||||
pop af
|
||||
|
||||
set_test 5,"HALT"
|
||||
wreg TAC,$05
|
||||
wreg TIMA,0
|
||||
wreg IF,0
|
||||
halt ; timer interrupt will exit halt
|
||||
nop ; avoids DMG bug
|
||||
lda IF
|
||||
and $04
|
||||
jp z,test_failed
|
||||
|
||||
jp tests_passed
|
||||
|
||||
.bank 0 slot 0
|
||||
.org $50
|
||||
inc a
|
||||
ret
|
||||
102
cpu_instrs/source/03-op sp,hl.s
Normal file
102
cpu_instrs/source/03-op sp,hl.s
Normal file
@@ -0,0 +1,102 @@
|
||||
; Tests SP/HL instructions
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
.byte $33,0,0 ; INC SP
|
||||
.byte $3B,0,0 ; DEC SP
|
||||
.byte $39,0,0 ; ADD HL,SP
|
||||
.byte $F9,0,0 ; LD SP,HL
|
||||
.byte $E8,$01,0 ; ADD SP,1
|
||||
.byte $E8,$FF,0 ; ADD SP,-1
|
||||
.byte $F8,$01,0 ; LD HL,SP+1
|
||||
.byte $F8,$FF,0 ; LD HL,SP-1
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
; C = flags register
|
||||
ld c,$00
|
||||
call test
|
||||
ld c,$F0
|
||||
call test
|
||||
ret
|
||||
|
||||
test:
|
||||
; Go through each value for HL
|
||||
ld hl,values
|
||||
hl_loop:
|
||||
ld e,(hl)
|
||||
inc hl
|
||||
ld d,(hl)
|
||||
inc hl
|
||||
push hl
|
||||
|
||||
; Go through each value for SP
|
||||
ld hl,values
|
||||
values_loop:
|
||||
push bc
|
||||
push de
|
||||
push hl
|
||||
|
||||
push bc
|
||||
pop af
|
||||
|
||||
; Switch stack
|
||||
ld (temp),sp
|
||||
ld a,(hl+)
|
||||
ld h,(hl)
|
||||
ld l,a
|
||||
; call print_regs
|
||||
ld sp,hl
|
||||
|
||||
; Set registers
|
||||
ld h,d
|
||||
ld l,e
|
||||
ld a,$12
|
||||
ld bc,$5691
|
||||
ld de,$9ABC
|
||||
|
||||
jp instr
|
||||
instr_done:
|
||||
; Save new SP and switch to yet another stack
|
||||
ld (temp+2),sp
|
||||
ld sp,$DF70
|
||||
|
||||
call checksum_af_bc_de_hl
|
||||
|
||||
; Checksum SP
|
||||
ld a,(temp+2)
|
||||
call update_crc_fast
|
||||
ld a,(temp+3)
|
||||
call update_crc_fast
|
||||
|
||||
ldsp temp
|
||||
|
||||
pop hl
|
||||
pop de
|
||||
pop bc
|
||||
inc hl
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,values_loop
|
||||
|
||||
pop hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,hl_loop
|
||||
|
||||
ret
|
||||
|
||||
values:
|
||||
.word $0000,$0001,$000F,$0010,$001F,$007F,$0080,$00FF
|
||||
.word $0100,$0F00,$1F00,$1000,$7FFF,$8000,$FFFF
|
||||
values_end:
|
||||
.word $0000,$0001,$000F,$0010,$001F,$007F,$0080,$00FF
|
||||
.word $0100,$0F00,$1F00,$1000,$7FFF,$8000,$FFFF
|
||||
|
||||
checksums:
|
||||
.byte $BC,$F4,$CD,$8C,$C7,$5E,$89,$E5,$36,$65,$21,$55,$D6,$6A,$2A,$FF
|
||||
.byte $EB,$34,$37,$B9,$08,$5F,$22,$13,$B6,$2A,$37,$C3,$72,$43,$5C,$4D
|
||||
88
cpu_instrs/source/04-op r,imm.s
Normal file
88
cpu_instrs/source/04-op r,imm.s
Normal file
@@ -0,0 +1,88 @@
|
||||
; Tests immediate instructions
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
.byte $36,0,0 ; LD (HL),$00
|
||||
.byte $06,0,0 ; LD B,$00
|
||||
.byte $0E,0,0 ; LD C,$00
|
||||
.byte $16,0,0 ; LD D,$00
|
||||
.byte $1E,0,0 ; LD E,$00
|
||||
.byte $26,0,0 ; LD H,$00
|
||||
.byte $2E,0,0 ; LD L,$00
|
||||
.byte $3E,0,0 ; LD A,$00
|
||||
.byte $F6,0,0 ; OR $00
|
||||
.byte $FE,0,0 ; CP $00
|
||||
.byte $C6,0,0 ; ADD $00
|
||||
.byte $CE,0,0 ; ADC $00
|
||||
.byte $D6,0,0 ; SUB $00
|
||||
.byte $DE,0,0 ; SBC $00
|
||||
.byte $E6,0,0 ; AND $00
|
||||
.byte $EE,0,0 ; XOR $00
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
ld c,$00
|
||||
call test
|
||||
ld c,$10
|
||||
call test
|
||||
ld c,$E0
|
||||
call test
|
||||
ld c,$F0
|
||||
call test
|
||||
ret
|
||||
|
||||
test:
|
||||
; Go through each value for A
|
||||
ld hl,values
|
||||
a_loop:
|
||||
ld b,(hl)
|
||||
push hl
|
||||
|
||||
; Go through each value for immediate data
|
||||
ld hl,values
|
||||
values_loop:
|
||||
push bc
|
||||
push hl
|
||||
|
||||
; Set registers
|
||||
push bc
|
||||
ld a,(hl)
|
||||
ld (instr+1),a
|
||||
ld bc,$1234
|
||||
ld de,$5678
|
||||
ld hl,rp_temp
|
||||
pop af
|
||||
|
||||
; call print_regs
|
||||
jp instr
|
||||
instr_done:
|
||||
|
||||
; Checksum registers and (hl)
|
||||
call checksum_af_bc_de_hl
|
||||
ld a,(rp_temp)
|
||||
call update_crc_fast
|
||||
|
||||
pop hl
|
||||
pop bc
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,values_loop
|
||||
|
||||
pop hl
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,a_loop
|
||||
|
||||
ret
|
||||
|
||||
values:
|
||||
.byte $00,$01,$0F,$10,$1F,$7F,$80,$F0,$FF
|
||||
values_end:
|
||||
|
||||
checksums:
|
||||
.byte $7F,$7F,$05,$B7,$85,$82,$94,$B6,$D8,$0A,$D6,$F5,$44,$8C,$37,$2A,$FB,$46,$05,$FA,$BD,$2F,$9E,$C1,$5A,$56,$2A,$DA,$D0,$EE,$14,$BA,$EA,$42,$36,$D2,$87,$28,$AB,$30,$4D,$A2,$63,$C6,$34,$4E,$55,$08,$9B,$1C,$97,$0E,$49,$F8,$73,$D4,$86,$C7,$DC,$C6,$03,$BF,$43,$21,
|
||||
98
cpu_instrs/source/05-op rp.s
Normal file
98
cpu_instrs/source/05-op rp.s
Normal file
@@ -0,0 +1,98 @@
|
||||
; Tests BC/DE/HL arithmetic
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
.byte $0B,0,0 ; DEC BC
|
||||
.byte $1B,0,0 ; DEC DE
|
||||
.byte $2B,0,0 ; DEC HL
|
||||
.byte $03,0,0 ; INC BC
|
||||
.byte $13,0,0 ; INC DE
|
||||
.byte $23,0,0 ; INC HL
|
||||
.byte $09,0,0 ; ADD HL,BC
|
||||
.byte $19,0,0 ; ADD HL,DE
|
||||
.byte $29,0,0 ; ADD HL,HL
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
ld c,$00
|
||||
call test
|
||||
ld c,$10
|
||||
call test
|
||||
ld c,$E0
|
||||
call test
|
||||
ld c,$F0
|
||||
call test
|
||||
ret
|
||||
|
||||
test:
|
||||
; Go through each value for HL
|
||||
ld hl,values
|
||||
hl_loop:
|
||||
ld e,(hl)
|
||||
inc hl
|
||||
ld d,(hl)
|
||||
inc hl
|
||||
push hl
|
||||
|
||||
; Go through each value for BC, DE, A
|
||||
ld hl,values
|
||||
values_loop:
|
||||
push bc
|
||||
push de
|
||||
push hl
|
||||
|
||||
push de
|
||||
push bc
|
||||
|
||||
; BC
|
||||
ld c,(hl)
|
||||
inc hl
|
||||
ld b,(hl)
|
||||
inc hl
|
||||
|
||||
; DE
|
||||
ld e,(hl)
|
||||
inc hl
|
||||
ld d,(hl)
|
||||
inc hl
|
||||
|
||||
; HL, AF
|
||||
pop af
|
||||
ld a,(hl)
|
||||
pop hl
|
||||
|
||||
; call print_regs
|
||||
jp instr
|
||||
instr_done:
|
||||
|
||||
; Checksum registers
|
||||
call checksum_af_bc_de_hl
|
||||
|
||||
pop hl
|
||||
pop de
|
||||
pop bc
|
||||
inc hl
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,values_loop
|
||||
|
||||
pop hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,hl_loop
|
||||
|
||||
ret
|
||||
|
||||
values:
|
||||
.word $0000,$0001,$000F,$0010,$001F,$007F,$0080,$00FF
|
||||
.word $0100,$0F00,$1F00,$1000,$7FFF,$8000,$FFFF
|
||||
values_end:
|
||||
.word $0000,$0001,$000F,$0010,$001F,$007F,$0080,$00FF
|
||||
.word $0100,$0F00,$1F00,$1000,$7FFF,$8000,$FFFF
|
||||
|
||||
checksums:
|
||||
.byte $C0,$A1,$36,$A3,$BE,$15,$B8,$2B,$9F,$93,$C6,$C2,$86,$C0,$07,$81,$0F,$75,$35,$38,$6B,$C7,$0A,$1B,$06,$68,$4B,$42,$64,$B4,$8C,$18,$FB,$6C,$31,$94,
|
||||
115
cpu_instrs/source/06-ld r,r.s
Normal file
115
cpu_instrs/source/06-ld r,r.s
Normal file
@@ -0,0 +1,115 @@
|
||||
; Tests LD r,r ($40-$7F)
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
.byte $40,0,0 ; LD B,B
|
||||
.byte $41,0,0 ; LD B,C
|
||||
.byte $42,0,0 ; LD B,D
|
||||
.byte $43,0,0 ; LD B,E
|
||||
.byte $44,0,0 ; LD B,H
|
||||
.byte $45,0,0 ; LD B,L
|
||||
.byte $46,0,0 ; LD B,(HL)
|
||||
.byte $47,0,0 ; LD B,A
|
||||
|
||||
.byte $48,0,0 ; LD C,B
|
||||
.byte $49,0,0 ; LD C,C
|
||||
.byte $4A,0,0 ; LD C,D
|
||||
.byte $4B,0,0 ; LD C,E
|
||||
.byte $4C,0,0 ; LD C,H
|
||||
.byte $4D,0,0 ; LD C,L
|
||||
.byte $4E,0,0 ; LD C,(HL)
|
||||
.byte $4F,0,0 ; LD C,A
|
||||
|
||||
.byte $50,0,0 ; LD D,B
|
||||
.byte $51,0,0 ; LD D,C
|
||||
.byte $52,0,0 ; LD D,D
|
||||
.byte $53,0,0 ; LD D,E
|
||||
.byte $54,0,0 ; LD D,H
|
||||
.byte $55,0,0 ; LD D,L
|
||||
.byte $56,0,0 ; LD D,(HL)
|
||||
.byte $57,0,0 ; LD D,A
|
||||
|
||||
.byte $58,0,0 ; LD E,B
|
||||
.byte $59,0,0 ; LD E,C
|
||||
.byte $5A,0,0 ; LD E,D
|
||||
.byte $5B,0,0 ; LD E,E
|
||||
.byte $5C,0,0 ; LD E,H
|
||||
.byte $5D,0,0 ; LD E,L
|
||||
.byte $5E,0,0 ; LD E,(HL)
|
||||
.byte $5F,0,0 ; LD E,A
|
||||
|
||||
.byte $60,0,0 ; LD H,B
|
||||
.byte $61,0,0 ; LD H,C
|
||||
.byte $62,0,0 ; LD H,D
|
||||
.byte $63,0,0 ; LD H,E
|
||||
.byte $64,0,0 ; LD H,H
|
||||
.byte $65,0,0 ; LD H,L
|
||||
.byte $66,0,0 ; LD H,(HL)
|
||||
.byte $67,0,0 ; LD H,A
|
||||
|
||||
.byte $68,0,0 ; LD L,B
|
||||
.byte $69,0,0 ; LD L,C
|
||||
.byte $6A,0,0 ; LD L,D
|
||||
.byte $6B,0,0 ; LD L,E
|
||||
.byte $6C,0,0 ; LD L,H
|
||||
.byte $6D,0,0 ; LD L,L
|
||||
.byte $6E,0,0 ; LD L,(HL)
|
||||
.byte $6F,0,0 ; LD L,A
|
||||
|
||||
.byte $70,0,0 ; LD (HL),B
|
||||
.byte $71,0,0 ; LD (HL),C
|
||||
.byte $72,0,0 ; LD (HL),D
|
||||
.byte $73,0,0 ; LD (HL),E
|
||||
.byte $74,0,0 ; LD (HL),H
|
||||
.byte $75,0,0 ; LD (HL),L
|
||||
.byte $77,0,0 ; LD (HL),A
|
||||
|
||||
.byte $78,0,0 ; LD A,B
|
||||
.byte $79,0,0 ; LD A,C
|
||||
.byte $7A,0,0 ; LD A,D
|
||||
.byte $7B,0,0 ; LD A,E
|
||||
.byte $7C,0,0 ; LD A,H
|
||||
.byte $7D,0,0 ; LD A,L
|
||||
.byte $7E,0,0 ; LD A,(HL)
|
||||
.byte $7F,0,0 ; LD A,A
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
ld c,$00
|
||||
call test
|
||||
ld c,$10
|
||||
call test
|
||||
ld c,$E0
|
||||
call test
|
||||
ld c,$F0
|
||||
call test
|
||||
ret
|
||||
|
||||
test:
|
||||
; Put different value in each register and (hl_temp)
|
||||
ld b,$BC
|
||||
push bc
|
||||
ld a,$DE
|
||||
ld (rp_temp),a
|
||||
ld a,$12
|
||||
ld bc,$3456
|
||||
ld de,$789A
|
||||
ld hl,rp_temp ; (HL) points to RAM
|
||||
pop af
|
||||
|
||||
; call print_regs
|
||||
jp instr
|
||||
instr_done:
|
||||
|
||||
; Checksum registers and (HL)
|
||||
call checksum_af_bc_de_hl
|
||||
ld a,(rp_temp)
|
||||
call update_crc_fast
|
||||
|
||||
ret
|
||||
|
||||
checksums:
|
||||
.byte $40,$3A,$AF,$06,$B6,$CB,$B2,$AB,$6F,$EF,$71,$9B,$75,$E3,$6C,$B9,$34,$FB,$26,$B7,$5A,$B9,$2F,$CE,$34,$FB,$26,$B7,$C2,$0A,$3B,$1A,$2A,$8A,$D6,$7C,$40,$3A,$AF,$06,$AF,$0A,$74,$70,$19,$A9,$6E,$6F,$11,$DA,$FE,$FE,$18,$10,$04,$2B,$11,$DA,$FE,$FE,$7B,$6A,$87,$84,$8B,$87,$34,$12,$00,$45,$DE,$01,$40,$3A,$AF,$06,$93,$E2,$8F,$C6,$DD,$7D,$90,$32,$FF,$90,$1B,$A8,$DD,$7D,$90,$32,$56,$BF,$7A,$21,$23,$C0,$FA,$06,$3B,$1D,$A0,$80,$3F,$44,$1B,$9C,$40,$3A,$AF,$06,$56,$25,$85,$CD,$D7,$B1,$DB,$F9,$56,$25,$85,$CD,$4E,$F8,$DF,$4B,$F0,$C3,$F9,$18,$20,$0F,$F6,$91,$71,$69,$CE,$46,$F0,$A0,$03,$4D,$40,$3A,$AF,$06,$29,$47,$E2,$36,$40,$3A,$AF,$06,$90,$F6,$A0,$8F,$3D,$62,$26,$A9,$A4,$52,$C1,$75,$45,$ED,$75,$40,$8A,$4D,$63,$56,$AF,$BA,$2D,$FE,$40,$3A,$AF,$06,$AF,$BA,$2D,$FE,$36,$8A,$CA,$22,$34,$8D,$C2,$65,$1A,$DB,$FF,$54,$32,$C0,$E8,$55,$ED,$4A,$87,$2F,$40,$3A,$AF,$06,$9D,$BC,$81,$E6,$6E,$6C,$92,$37,$B1,$EC,$C3,$29,$1D,$C5,$9F,$A1,$59,$6F,$66,$CD,$B4,$FB,$FD,$74,$EC,$13,$F3,$8E,$70,$0C,$5F,$ED,$EC,$13,$F3,$8E,$40,$3A,$AF,$06,
|
||||
127
cpu_instrs/source/07-jr,jp,call,ret,rst.s
Normal file
127
cpu_instrs/source/07-jr,jp,call,ret,rst.s
Normal file
@@ -0,0 +1,127 @@
|
||||
; Tests branch instructions
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
; JR cond,skip
|
||||
; INC A
|
||||
; skip:
|
||||
.byte $18,$01,$3C ; JR *+3
|
||||
.byte $20,$01,$3C ; JR NZ,*+3
|
||||
.byte $28,$01,$3C ; JR Z,*+3
|
||||
.byte $30,$01,$3C ; JR NC,*+3
|
||||
.byte $38,$01,$3C ; JR C,*+3
|
||||
|
||||
.byte $C2,<taken,>taken ; JP NZ,taken
|
||||
.byte $C3,<taken,>taken ; JP taken
|
||||
.byte $CA,<taken,>taken ; JP Z,taken
|
||||
.byte $D2,<taken,>taken ; JP NC,taken
|
||||
.byte $DA,<taken,>taken ; JP C,taken
|
||||
|
||||
.byte $C4,<taken,>taken ; CALL NZ,taken
|
||||
.byte $CC,<taken,>taken ; CALL Z,taken
|
||||
.byte $CD,<taken,>taken ; CALL taken
|
||||
.byte $D4,<taken,>taken ; CALL NC,taken
|
||||
.byte $DC,<taken,>taken ; CALL C,taken
|
||||
|
||||
; RET cond
|
||||
; INC A
|
||||
.byte $C0,$3C,0 ; RET NZ
|
||||
.byte $C8,$3C,0 ; RET Z
|
||||
.byte $C9,$3C,0 ; RET
|
||||
.byte $D0,$3C,0 ; RET NC
|
||||
.byte $D8,$3C,0 ; RET C
|
||||
.byte $D9,$3C,0 ; RETI
|
||||
|
||||
; RST
|
||||
; can only easily test this one on devcart
|
||||
.byte $C7,0,0 ; RST $00
|
||||
.ifndef BUILD_DEVCART
|
||||
.byte $CF,0,0 ; RST $08
|
||||
.byte $D7,0,0 ; RST $10
|
||||
.byte $DF,0,0 ; RST $18
|
||||
.byte $E7,0,0 ; RST $20
|
||||
.byte $EF,0,0 ; RST $28
|
||||
.byte $F7,0,0 ; RST $30
|
||||
.byte $FF,0,0 ; RST $38
|
||||
.endif
|
||||
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
wreg IE,0 ; disable interrupts, since RETI does EI
|
||||
|
||||
; Go through all 16 combinations of flags
|
||||
ld bc,$1200
|
||||
-
|
||||
; Fill 4 bytes of new stack
|
||||
ld a,$12
|
||||
ld ($DF80-2),a
|
||||
ld a,$34
|
||||
ld ($DF80-3),a
|
||||
ld a,$56
|
||||
ld ($DF80-4),a
|
||||
ld a,$78
|
||||
ld ($DF80-5),a
|
||||
|
||||
; Set AF
|
||||
push bc
|
||||
pop af
|
||||
|
||||
; Switch to new stack
|
||||
ld (temp),sp
|
||||
ld sp,$DF80
|
||||
|
||||
; Set return address
|
||||
ld de,instr+3
|
||||
push de
|
||||
|
||||
jp instr
|
||||
instr_done:
|
||||
inc a
|
||||
taken:
|
||||
di ; RETI enables interrupts
|
||||
|
||||
; Save new SP and switch to yet another stack
|
||||
ld (temp+2),sp
|
||||
ld sp,$DF70
|
||||
|
||||
; Checksum A and SP
|
||||
call update_crc_fast
|
||||
ld a,(temp+2)
|
||||
call update_crc_fast
|
||||
ld a,(temp+3)
|
||||
call update_crc_fast
|
||||
|
||||
; Checksum 4 bytes of stack
|
||||
ld a,($DF80-2)
|
||||
call update_crc_fast
|
||||
ld a,($DF80-3)
|
||||
call update_crc_fast
|
||||
ld a,($DF80-4)
|
||||
call update_crc_fast
|
||||
ld a,($DF80-5)
|
||||
call update_crc_fast
|
||||
|
||||
ldsp temp
|
||||
|
||||
ld a,c
|
||||
add $10
|
||||
ld c,a
|
||||
jr nz,-
|
||||
|
||||
ret
|
||||
|
||||
checksums:
|
||||
.byte $EC,$A4,$94,$79,$C4,$00,$96,$2C,$C4,$64,$90,$33,$77,$C7,$0A,$D4
|
||||
.byte $77,$A3,$0C,$CB,$79,$E7,$7E,$AE,$DA,$DC,$03,$F7,$4F,$9F,$E9,$20
|
||||
.byte $72,$12,$DA,$01,$44,$6A,$4D,$8F,$D1,$79,$30,$4C,$AA,$37,$F2,$6A
|
||||
.byte $97,$EA,$56,$5F,$32,$28,$C7,$D1,$49,$66,$05,$F7,$80,$0F,$BA,$8E
|
||||
.byte $41,$E2,$A4,$9A,$2D,$2D,$8C,$72,$A5,$13,$76,$A8,$64,$FE,$68,$BC
|
||||
.byte $2D,$2D,$8C,$72,$50,$96,$24,$27,$50,$96,$24,$27,$50,$96,$24,$27
|
||||
.byte $50,$96,$24,$27,$50,$96,$24,$27,$50,$96,$24,$27,$50,$96,$24,$27
|
||||
.byte $50,$96,$24,$27
|
||||
|
||||
.include "multi_custom.s"
|
||||
110
cpu_instrs/source/08-misc instrs.s
Normal file
110
cpu_instrs/source/08-misc instrs.s
Normal file
@@ -0,0 +1,110 @@
|
||||
; Tests miscellaneous instructions
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
.byte $F0,$91,0 ; LDH A,($91)
|
||||
.byte $E0,$91,0 ; LDH ($91),A
|
||||
.byte $F2,$00,0 ; LDH A,(C)
|
||||
.byte $E2,$00,0 ; LDH (C),A
|
||||
.byte $FA,$91,$FF ; LD A,($FF91)
|
||||
.byte $EA,$91,$FF ; LD ($FF91),A
|
||||
.byte $08,$91,$FF ; LD ($FF91),SP
|
||||
.byte $01,$23,$01 ; LD BC,$0123
|
||||
.byte $11,$23,$01 ; LD DE,$0123
|
||||
.byte $21,$23,$01 ; LD HL,$0123
|
||||
.byte $31,$23,$01 ; LD SP,$0123
|
||||
.byte $F5,0,0 ; PUSH AF
|
||||
.byte $C5,0,0 ; PUSH BC
|
||||
.byte $D5,0,0 ; PUSH DE
|
||||
.byte $E5,0,0 ; PUSH HL
|
||||
.byte $F1,0,0 ; POP AF
|
||||
.byte $C1,0,0 ; POP BC
|
||||
.byte $D1,0,0 ; POP DE
|
||||
.byte $E1,0,0 ; POP HL
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
; C = flags register
|
||||
ld c,$00
|
||||
call test
|
||||
ld c,$10
|
||||
call test
|
||||
ld c,$E0
|
||||
call test
|
||||
ld c,$F0
|
||||
call test
|
||||
ret
|
||||
|
||||
test:
|
||||
; Fill RAM
|
||||
ld a,$FE
|
||||
ld ($FF90),a
|
||||
ld a,$DC
|
||||
ld ($FF91),a
|
||||
ld a,$BA
|
||||
ld ($FF92),a
|
||||
|
||||
; Fill stack
|
||||
ld a,$13
|
||||
ld ($DF80),a
|
||||
ld a,$57
|
||||
ld ($DF80-1),a
|
||||
ld a,$9B
|
||||
ld ($DF80-2),a
|
||||
ld a,$DF
|
||||
ld ($DF80-3),a
|
||||
|
||||
; Set registers
|
||||
ld b,$12
|
||||
push bc
|
||||
ld bc,$5691
|
||||
ld de,$9ABC
|
||||
ld hl,$DEF0
|
||||
pop af
|
||||
|
||||
; Switch stack
|
||||
ld (temp),sp
|
||||
ld sp,$DF80-2
|
||||
|
||||
jp instr
|
||||
instr_done:
|
||||
; Save new SP and switch to another stack
|
||||
ld (temp+2),sp
|
||||
ld sp,$DF70
|
||||
|
||||
call checksum_af_bc_de_hl
|
||||
|
||||
; Checksum SP
|
||||
ld a,(temp+2)
|
||||
call update_crc_fast
|
||||
ld a,(temp+3)
|
||||
call update_crc_fast
|
||||
|
||||
; Checksum RAM
|
||||
ld a,($FF90)
|
||||
call update_crc_fast
|
||||
ld a,($FF91)
|
||||
call update_crc_fast
|
||||
ld a,($FF92)
|
||||
call update_crc_fast
|
||||
|
||||
; Checksum stack
|
||||
ld a,($DF80)
|
||||
call update_crc_fast
|
||||
ld a,($DF80-1)
|
||||
call update_crc_fast
|
||||
ld a,($DF80-2)
|
||||
call update_crc_fast
|
||||
ld a,($DF80-3)
|
||||
call update_crc_fast
|
||||
|
||||
; Restore SP
|
||||
ldsp temp
|
||||
|
||||
ret
|
||||
|
||||
checksums:
|
||||
.byte $4D,$FF,$15,$97,$6D,$A7,$35,$65,$4D,$FF,$15,$97,$6D,$A7,$35,$65,$4D,$FF,$15,$97,$6D,$A7,$35,$65,$AD,$FA,$5E,$41,$D0,$78,$79,$C1,$AF,$66,$99,$34,$0D,$E1,$97,$99,$6F,$D0,$6F,$5D,$C3,$1F,$A3,$8A,$C2,$F1,$9C,$F3,$C1,$C3,$DC,$78,$C0,$2D,$E3,$01,$8F,$C4,$0F,$44,$95,$22,$6A,$39,$61,$C5,$AB,$55,$FB,$DF,$2C,$52,
|
||||
269
cpu_instrs/source/09-op r,r.s
Normal file
269
cpu_instrs/source/09-op r,r.s
Normal file
@@ -0,0 +1,269 @@
|
||||
; Tests most register instructions.
|
||||
; Takes 10 seconds.
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
.byte $00,0,0 ; NOP
|
||||
.byte $2F,0,0 ; CPL
|
||||
.byte $37,0,0 ; SCF
|
||||
.byte $3F,0,0 ; CCF
|
||||
|
||||
.byte $B0,0,0 ; OR B
|
||||
.byte $B1,0,0 ; OR C
|
||||
.byte $B2,0,0 ; OR D
|
||||
.byte $B3,0,0 ; OR E
|
||||
.byte $B4,0,0 ; OR H
|
||||
.byte $B5,0,0 ; OR L
|
||||
.byte $B7,0,0 ; OR A
|
||||
|
||||
.byte $B8,0,0 ; CP B
|
||||
.byte $B9,0,0 ; CP C
|
||||
.byte $BA,0,0 ; CP D
|
||||
.byte $BB,0,0 ; CP E
|
||||
.byte $BC,0,0 ; CP H
|
||||
.byte $BD,0,0 ; CP L
|
||||
.byte $BF,0,0 ; CP A
|
||||
|
||||
.byte $80,0,0 ; ADD B
|
||||
.byte $81,0,0 ; ADD C
|
||||
.byte $82,0,0 ; ADD D
|
||||
.byte $83,0,0 ; ADD E
|
||||
.byte $84,0,0 ; ADD H
|
||||
.byte $85,0,0 ; ADD L
|
||||
.byte $87,0,0 ; ADD A
|
||||
|
||||
.byte $88,0,0 ; ADC B
|
||||
.byte $89,0,0 ; ADC C
|
||||
.byte $8A,0,0 ; ADC D
|
||||
.byte $8B,0,0 ; ADC E
|
||||
.byte $8C,0,0 ; ADC H
|
||||
.byte $8D,0,0 ; ADC L
|
||||
.byte $8F,0,0 ; ADC A
|
||||
|
||||
.byte $90,0,0 ; SUB B
|
||||
.byte $91,0,0 ; SUB C
|
||||
.byte $92,0,0 ; SUB D
|
||||
.byte $93,0,0 ; SUB E
|
||||
.byte $94,0,0 ; SUB H
|
||||
.byte $95,0,0 ; SUB L
|
||||
.byte $97,0,0 ; SUB A
|
||||
|
||||
.byte $98,0,0 ; SBC B
|
||||
.byte $99,0,0 ; SBC C
|
||||
.byte $9A,0,0 ; SBC D
|
||||
.byte $9B,0,0 ; SBC E
|
||||
.byte $9C,0,0 ; SBC H
|
||||
.byte $9D,0,0 ; SBC L
|
||||
.byte $9F,0,0 ; SBC A
|
||||
|
||||
.byte $A0,0,0 ; AND B
|
||||
.byte $A1,0,0 ; AND C
|
||||
.byte $A2,0,0 ; AND D
|
||||
.byte $A3,0,0 ; AND E
|
||||
.byte $A4,0,0 ; AND H
|
||||
.byte $A5,0,0 ; AND L
|
||||
.byte $A7,0,0 ; AND A
|
||||
|
||||
.byte $A8,0,0 ; XOR B
|
||||
.byte $A9,0,0 ; XOR C
|
||||
.byte $AA,0,0 ; XOR D
|
||||
.byte $AB,0,0 ; XOR E
|
||||
.byte $AC,0,0 ; XOR H
|
||||
.byte $AD,0,0 ; XOR L
|
||||
.byte $AF,0,0 ; XOR A
|
||||
|
||||
.byte $05,0,0 ; DEC B
|
||||
.byte $0D,0,0 ; DEC C
|
||||
.byte $15,0,0 ; DEC D
|
||||
.byte $1D,0,0 ; DEC E
|
||||
.byte $25,0,0 ; DEC H
|
||||
.byte $2D,0,0 ; DEC L
|
||||
.byte $3D,0,0 ; DEC A
|
||||
|
||||
.byte $04,0,0 ; INC B
|
||||
.byte $0C,0,0 ; INC C
|
||||
.byte $14,0,0 ; INC D
|
||||
.byte $1C,0,0 ; INC E
|
||||
.byte $24,0,0 ; INC H
|
||||
.byte $2C,0,0 ; INC L
|
||||
.byte $3C,0,0 ; INC A
|
||||
|
||||
.byte $07,0,0 ; RLCA
|
||||
.byte $17,0,0 ; RLA
|
||||
.byte $0F,0,0 ; RRCA
|
||||
.byte $1F,0,0 ; RRA
|
||||
|
||||
.byte $CB,$00,0 ; RLC B
|
||||
.byte $CB,$01,0 ; RLC C
|
||||
.byte $CB,$02,0 ; RLC D
|
||||
.byte $CB,$03,0 ; RLC E
|
||||
.byte $CB,$04,0 ; RLC H
|
||||
.byte $CB,$05,0 ; RLC L
|
||||
.byte $CB,$07,0 ; RLC A
|
||||
|
||||
.byte $CB,$08,0 ; RRC B
|
||||
.byte $CB,$09,0 ; RRC C
|
||||
.byte $CB,$0A,0 ; RRC D
|
||||
.byte $CB,$0B,0 ; RRC E
|
||||
.byte $CB,$0C,0 ; RRC H
|
||||
.byte $CB,$0D,0 ; RRC L
|
||||
.byte $CB,$0F,0 ; RRC A
|
||||
|
||||
.byte $CB,$10,0 ; RL B
|
||||
.byte $CB,$11,0 ; RL C
|
||||
.byte $CB,$12,0 ; RL D
|
||||
.byte $CB,$13,0 ; RL E
|
||||
.byte $CB,$14,0 ; RL H
|
||||
.byte $CB,$15,0 ; RL L
|
||||
.byte $CB,$17,0 ; RL A
|
||||
|
||||
.byte $CB,$18,0 ; RR B
|
||||
.byte $CB,$19,0 ; RR C
|
||||
.byte $CB,$1A,0 ; RR D
|
||||
.byte $CB,$1B,0 ; RR E
|
||||
.byte $CB,$1C,0 ; RR H
|
||||
.byte $CB,$1D,0 ; RR L
|
||||
.byte $CB,$1F,0 ; RR A
|
||||
|
||||
.byte $CB,$20,0 ; SLA B
|
||||
.byte $CB,$21,0 ; SLA C
|
||||
.byte $CB,$22,0 ; SLA D
|
||||
.byte $CB,$23,0 ; SLA E
|
||||
.byte $CB,$24,0 ; SLA H
|
||||
.byte $CB,$25,0 ; SLA L
|
||||
.byte $CB,$27,0 ; SLA A
|
||||
|
||||
.byte $CB,$28,0 ; SRA B
|
||||
.byte $CB,$29,0 ; SRA C
|
||||
.byte $CB,$2A,0 ; SRA D
|
||||
.byte $CB,$2B,0 ; SRA E
|
||||
.byte $CB,$2C,0 ; SRA H
|
||||
.byte $CB,$2D,0 ; SRA L
|
||||
.byte $CB,$2F,0 ; SRA A
|
||||
|
||||
.byte $CB,$30,0 ; SWAP B
|
||||
.byte $CB,$31,0 ; SWAP C
|
||||
.byte $CB,$32,0 ; SWAP D
|
||||
.byte $CB,$33,0 ; SWAP E
|
||||
.byte $CB,$34,0 ; SWAP H
|
||||
.byte $CB,$35,0 ; SWAP L
|
||||
.byte $CB,$37,0 ; SWAP A
|
||||
|
||||
.byte $CB,$38,0 ; SRL B
|
||||
.byte $CB,$39,0 ; SRL C
|
||||
.byte $CB,$3A,0 ; SRL D
|
||||
.byte $CB,$3B,0 ; SRL E
|
||||
.byte $CB,$3C,0 ; SRL H
|
||||
.byte $CB,$3D,0 ; SRL L
|
||||
.byte $CB,$3F,0 ; SRL A
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
ld c,$00
|
||||
call test
|
||||
ld c,$F0
|
||||
call test
|
||||
ret
|
||||
|
||||
test:
|
||||
; Go through each value for A
|
||||
ld hl,values
|
||||
a_loop:
|
||||
ld b,(hl)
|
||||
push hl
|
||||
|
||||
; Go through each value for other registers
|
||||
ld hl,values
|
||||
values_loop:
|
||||
push bc
|
||||
push hl
|
||||
|
||||
push bc
|
||||
|
||||
; BC
|
||||
ld a,(hl+)
|
||||
ld b,a
|
||||
ld a,(hl+)
|
||||
ld c,a
|
||||
|
||||
; HL
|
||||
ld a,(hl+)
|
||||
ld d,a
|
||||
ld a,(hl+)
|
||||
ld e,a
|
||||
push de
|
||||
|
||||
; DE
|
||||
ld a,(hl+)
|
||||
ld d,a
|
||||
ld a,(hl+)
|
||||
ld e,a
|
||||
|
||||
pop hl
|
||||
pop af
|
||||
|
||||
; call print_regs
|
||||
jp instr
|
||||
instr_done:
|
||||
|
||||
; Checksum registers
|
||||
call checksum_af_bc_de_hl
|
||||
|
||||
pop hl
|
||||
pop bc
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,values_loop
|
||||
|
||||
pop hl
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,a_loop
|
||||
|
||||
ret
|
||||
|
||||
values:
|
||||
.byte $00,$01,$0F,$10,$1F,$7F,$80,$F0,$FF
|
||||
values_end:
|
||||
.byte $00,$01,$0F,$10,$1F,$7F,$80,$F0,$FF
|
||||
|
||||
checksums:
|
||||
.byte $7C,$55,$BD,$05,$BA,$C7,$AC,$D1,$74,$6D,$82,$4A,$0F,$06,$2A,$C5
|
||||
.byte $FA,$97,$9B,$9D,$C3,$32,$A0,$78,$00,$C1,$9F,$69,$C0,$D1,$C2,$A1
|
||||
.byte $55,$0D,$3F,$C8,$09,$7D,$97,$92,$CE,$66,$30,$56,$95,$F3,$01,$A1
|
||||
.byte $5B,$97,$54,$4C,$56,$FC,$A0,$89,$42,$F8,$7B,$2A,$E6,$7C,$03,$40
|
||||
.byte $45,$60,$C5,$A8,$B7,$BF,$B0,$EF,$A0,$7A,$1B,$4F,$FB,$22,$B4,$33
|
||||
.byte $06,$3D,$B5,$C7,$3C,$A4,$D5,$23,$C1,$BE,$75,$8B,$E0,$9B,$98,$BB
|
||||
.byte $0E,$75,$D9,$E6,$82,$A7,$E2,$66,$CD,$78,$4F,$E8,$8E,$D4,$2D,$3E
|
||||
.byte $88,$5C,$58,$C7,$F9,$20,$5F,$B9,$A8,$E4,$CA,$5E,$C8,$DB,$88,$94
|
||||
.byte $A3,$0D,$87,$60,$8B,$BA,$2B,$27,$41,$88,$83,$B1,$0A,$41,$9E,$D6
|
||||
.byte $98,$8D,$19,$B7,$13,$C6,$D5,$BF,$83,$CE,$74,$9F,$00,$34,$07,$5E
|
||||
.byte $F0,$E1,$1A,$68,$8F,$BA,$85,$A7,$A0,$46,$06,$A5,$75,$F9,$83,$48
|
||||
.byte $12,$EF,$1B,$03,$C8,$FB,$79,$EA,$9B,$00,$6C,$A9,$0D,$5E,$CB,$57
|
||||
.byte $41,$1B,$4B,$0C,$B2,$08,$D8,$E3,$43,$07,$E1,$93,$34,$73,$23,$C9
|
||||
.byte $18,$2F,$38,$F9,$D1,$3B,$AB,$5A,$BF,$C6,$F8,$03,$50,$0C,$A4,$32
|
||||
.byte $6B,$06,$7E,$FE,$ED,$8B,$D4,$15,$29,$46,$6D,$24,$6E,$5B,$15,$1A
|
||||
.byte $32,$AE,$87,$B0,$DC,$20,$AC,$4B,$2B,$63,$60,$C7,$C1,$92,$75,$AA
|
||||
.byte $6F,$CA,$17,$53,$5A,$C5,$78,$EA,$61,$01,$10,$83,$DD,$08,$D8,$78
|
||||
.byte $CA,$0B,$F5,$1F,$92,$55,$08,$01,$7F,$EA,$CD,$9B,$2A,$AA,$73,$17
|
||||
.byte $E0,$9F,$D0,$BA,$E7,$73,$72,$3D,$B7,$95,$2F,$3B,$A7,$78,$50,$36
|
||||
.byte $81,$04,$5B,$9E,$9A,$DE,$A4,$DD,$21,$B2,$9B,$36,$9F,$D7,$C8,$32
|
||||
.byte $48,$0E,$FC,$E5,$55,$C3,$53,$75,$A4,$ED,$A9,$E0,$9E,$78,$A7,$1D
|
||||
.byte $B8,$F4,$7C,$D6,$90,$2A,$03,$87,$81,$D8,$D5,$90,$63,$02,$C4,$52
|
||||
.byte $C2,$BE,$85,$B3,$32,$9A,$9E,$2D,$E3,$FB,$22,$47,$8E,$65,$08,$73
|
||||
.byte $72,$5A,$73,$95,$ED,$EC,$59,$9D,$C8,$67,$68,$F1,$4B,$ED,$41,$D5
|
||||
.byte $68,$39,$75,$F3,$FC,$09,$EF,$0D,$20,$2B,$43,$A3,$69,$AA,$89,$4F
|
||||
.byte $84,$87,$7B,$58,$42,$0A,$56,$EF,$1B,$0E,$19,$CA,$6F,$1B,$F9,$17
|
||||
.byte $EA,$B6,$4C,$B2,$1A,$C4,$C0,$B1,$E2,$B2,$45,$4E,$91,$0A,$8D,$AE
|
||||
.byte $17,$31,$55,$A3,$1B,$69,$72,$D8,$03,$E9,$55,$8D,$87,$27,$36,$63
|
||||
.byte $E6,$85,$12,$D1,$F2,$32,$97,$4D,$B5,$FA,$08,$A9,$97,$2A,$5A,$C2
|
||||
.byte $FD,$2D,$A4,$27,$57,$7C,$EC,$BD,$CC,$67,$19,$21,$46,$D4,$CD,$D6
|
||||
.byte $CB,$55,$D4,$E2,$9E,$F3,$32,$2E,$AA,$F8,$BB,$B3,$F6,$3A,$CC,$08
|
||||
.byte $64,$8B,$C2,$5F,$58,$66,$AF,$67,$B3,$44,$2C,$66,$72,$E7,$3B,$3F
|
||||
.byte $5B,$87,$0C,$17,$58,$E2,$B4,$A0,$70,$18,$81,$E6,$42,$56,$12,$CE
|
||||
.byte $BB,$13,$46,$3C,$BE,$5A,$FB,$53
|
||||
315
cpu_instrs/source/10-bit ops.s
Normal file
315
cpu_instrs/source/10-bit ops.s
Normal file
@@ -0,0 +1,315 @@
|
||||
; Tests most register instructions.
|
||||
; Takes 15 seconds.
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
.byte $CB,$40,0 ; BIT 0,B
|
||||
.byte $CB,$41,0 ; BIT 0,C
|
||||
.byte $CB,$42,0 ; BIT 0,D
|
||||
.byte $CB,$43,0 ; BIT 0,E
|
||||
.byte $CB,$44,0 ; BIT 0,H
|
||||
.byte $CB,$45,0 ; BIT 0,L
|
||||
.byte $CB,$47,0 ; BIT 0,A
|
||||
|
||||
.byte $CB,$48,0 ; BIT 1,B
|
||||
.byte $CB,$49,0 ; BIT 1,C
|
||||
.byte $CB,$4A,0 ; BIT 1,D
|
||||
.byte $CB,$4B,0 ; BIT 1,E
|
||||
.byte $CB,$4C,0 ; BIT 1,H
|
||||
.byte $CB,$4D,0 ; BIT 1,L
|
||||
.byte $CB,$4F,0 ; BIT 1,A
|
||||
|
||||
.byte $CB,$50,0 ; BIT 2,B
|
||||
.byte $CB,$51,0 ; BIT 2,C
|
||||
.byte $CB,$52,0 ; BIT 2,D
|
||||
.byte $CB,$53,0 ; BIT 2,E
|
||||
.byte $CB,$54,0 ; BIT 2,H
|
||||
.byte $CB,$55,0 ; BIT 2,L
|
||||
.byte $CB,$57,0 ; BIT 2,A
|
||||
|
||||
.byte $CB,$58,0 ; BIT 3,B
|
||||
.byte $CB,$59,0 ; BIT 3,C
|
||||
.byte $CB,$5A,0 ; BIT 3,D
|
||||
.byte $CB,$5B,0 ; BIT 3,E
|
||||
.byte $CB,$5C,0 ; BIT 3,H
|
||||
.byte $CB,$5D,0 ; BIT 3,L
|
||||
.byte $CB,$5F,0 ; BIT 3,A
|
||||
|
||||
.byte $CB,$60,0 ; BIT 4,B
|
||||
.byte $CB,$61,0 ; BIT 4,C
|
||||
.byte $CB,$62,0 ; BIT 4,D
|
||||
.byte $CB,$63,0 ; BIT 4,E
|
||||
.byte $CB,$64,0 ; BIT 4,H
|
||||
.byte $CB,$65,0 ; BIT 4,L
|
||||
.byte $CB,$67,0 ; BIT 4,A
|
||||
|
||||
.byte $CB,$68,0 ; BIT 5,B
|
||||
.byte $CB,$69,0 ; BIT 5,C
|
||||
.byte $CB,$6A,0 ; BIT 5,D
|
||||
.byte $CB,$6B,0 ; BIT 5,E
|
||||
.byte $CB,$6C,0 ; BIT 5,H
|
||||
.byte $CB,$6D,0 ; BIT 5,L
|
||||
.byte $CB,$6F,0 ; BIT 5,A
|
||||
|
||||
.byte $CB,$70,0 ; BIT 6,B
|
||||
.byte $CB,$71,0 ; BIT 6,C
|
||||
.byte $CB,$72,0 ; BIT 6,D
|
||||
.byte $CB,$73,0 ; BIT 6,E
|
||||
.byte $CB,$74,0 ; BIT 6,H
|
||||
.byte $CB,$75,0 ; BIT 6,L
|
||||
.byte $CB,$77,0 ; BIT 6,A
|
||||
|
||||
.byte $CB,$78,0 ; BIT 7,B
|
||||
.byte $CB,$79,0 ; BIT 7,C
|
||||
.byte $CB,$7A,0 ; BIT 7,D
|
||||
.byte $CB,$7B,0 ; BIT 7,E
|
||||
.byte $CB,$7C,0 ; BIT 7,H
|
||||
.byte $CB,$7D,0 ; BIT 7,L
|
||||
.byte $CB,$7F,0 ; BIT 7,A
|
||||
|
||||
.byte $CB,$80,0 ; RES 0,B
|
||||
.byte $CB,$81,0 ; RES 0,C
|
||||
.byte $CB,$82,0 ; RES 0,D
|
||||
.byte $CB,$83,0 ; RES 0,E
|
||||
.byte $CB,$84,0 ; RES 0,H
|
||||
.byte $CB,$85,0 ; RES 0,L
|
||||
.byte $CB,$87,0 ; RES 0,A
|
||||
|
||||
.byte $CB,$88,0 ; RES 1,B
|
||||
.byte $CB,$89,0 ; RES 1,C
|
||||
.byte $CB,$8A,0 ; RES 1,D
|
||||
.byte $CB,$8B,0 ; RES 1,E
|
||||
.byte $CB,$8C,0 ; RES 1,H
|
||||
.byte $CB,$8D,0 ; RES 1,L
|
||||
.byte $CB,$8F,0 ; RES 1,A
|
||||
|
||||
.byte $CB,$90,0 ; RES 2,B
|
||||
.byte $CB,$91,0 ; RES 2,C
|
||||
.byte $CB,$92,0 ; RES 2,D
|
||||
.byte $CB,$93,0 ; RES 2,E
|
||||
.byte $CB,$94,0 ; RES 2,H
|
||||
.byte $CB,$95,0 ; RES 2,L
|
||||
.byte $CB,$97,0 ; RES 2,A
|
||||
|
||||
.byte $CB,$98,0 ; RES 3,B
|
||||
.byte $CB,$99,0 ; RES 3,C
|
||||
.byte $CB,$9A,0 ; RES 3,D
|
||||
.byte $CB,$9B,0 ; RES 3,E
|
||||
.byte $CB,$9C,0 ; RES 3,H
|
||||
.byte $CB,$9D,0 ; RES 3,L
|
||||
.byte $CB,$9F,0 ; RES 3,A
|
||||
|
||||
.byte $CB,$A0,0 ; RES 4,B
|
||||
.byte $CB,$A1,0 ; RES 4,C
|
||||
.byte $CB,$A2,0 ; RES 4,D
|
||||
.byte $CB,$A3,0 ; RES 4,E
|
||||
.byte $CB,$A4,0 ; RES 4,H
|
||||
.byte $CB,$A5,0 ; RES 4,L
|
||||
.byte $CB,$A7,0 ; RES 4,A
|
||||
|
||||
.byte $CB,$A8,0 ; RES 5,B
|
||||
.byte $CB,$A9,0 ; RES 5,C
|
||||
.byte $CB,$AA,0 ; RES 5,D
|
||||
.byte $CB,$AB,0 ; RES 5,E
|
||||
.byte $CB,$AC,0 ; RES 5,H
|
||||
.byte $CB,$AD,0 ; RES 5,L
|
||||
.byte $CB,$AF,0 ; RES 5,A
|
||||
|
||||
.byte $CB,$B0,0 ; RES 6,B
|
||||
.byte $CB,$B1,0 ; RES 6,C
|
||||
.byte $CB,$B2,0 ; RES 6,D
|
||||
.byte $CB,$B3,0 ; RES 6,E
|
||||
.byte $CB,$B4,0 ; RES 6,H
|
||||
.byte $CB,$B5,0 ; RES 6,L
|
||||
.byte $CB,$B7,0 ; RES 6,A
|
||||
|
||||
.byte $CB,$B8,0 ; RES 7,B
|
||||
.byte $CB,$B9,0 ; RES 7,C
|
||||
.byte $CB,$BA,0 ; RES 7,D
|
||||
.byte $CB,$BB,0 ; RES 7,E
|
||||
.byte $CB,$BC,0 ; RES 7,H
|
||||
.byte $CB,$BD,0 ; RES 7,L
|
||||
.byte $CB,$BF,0 ; RES 7,A
|
||||
|
||||
.byte $CB,$C0,0 ; SET 0,B
|
||||
.byte $CB,$C1,0 ; SET 0,C
|
||||
.byte $CB,$C2,0 ; SET 0,D
|
||||
.byte $CB,$C3,0 ; SET 0,E
|
||||
.byte $CB,$C4,0 ; SET 0,H
|
||||
.byte $CB,$C5,0 ; SET 0,L
|
||||
.byte $CB,$C7,0 ; SET 0,A
|
||||
|
||||
.byte $CB,$C8,0 ; SET 1,B
|
||||
.byte $CB,$C9,0 ; SET 1,C
|
||||
.byte $CB,$CA,0 ; SET 1,D
|
||||
.byte $CB,$CB,0 ; SET 1,E
|
||||
.byte $CB,$CC,0 ; SET 1,H
|
||||
.byte $CB,$CD,0 ; SET 1,L
|
||||
.byte $CB,$CF,0 ; SET 1,A
|
||||
|
||||
.byte $CB,$D0,0 ; SET 2,B
|
||||
.byte $CB,$D1,0 ; SET 2,C
|
||||
.byte $CB,$D2,0 ; SET 2,D
|
||||
.byte $CB,$D3,0 ; SET 2,E
|
||||
.byte $CB,$D4,0 ; SET 2,H
|
||||
.byte $CB,$D5,0 ; SET 2,L
|
||||
.byte $CB,$D7,0 ; SET 2,A
|
||||
|
||||
.byte $CB,$D8,0 ; SET 3,B
|
||||
.byte $CB,$D9,0 ; SET 3,C
|
||||
.byte $CB,$DA,0 ; SET 3,D
|
||||
.byte $CB,$DB,0 ; SET 3,E
|
||||
.byte $CB,$DC,0 ; SET 3,H
|
||||
.byte $CB,$DD,0 ; SET 3,L
|
||||
.byte $CB,$DF,0 ; SET 3,A
|
||||
|
||||
.byte $CB,$E0,0 ; SET 4,B
|
||||
.byte $CB,$E1,0 ; SET 4,C
|
||||
.byte $CB,$E2,0 ; SET 4,D
|
||||
.byte $CB,$E3,0 ; SET 4,E
|
||||
.byte $CB,$E4,0 ; SET 4,H
|
||||
.byte $CB,$E5,0 ; SET 4,L
|
||||
.byte $CB,$E7,0 ; SET 4,A
|
||||
|
||||
.byte $CB,$E8,0 ; SET 5,B
|
||||
.byte $CB,$E9,0 ; SET 5,C
|
||||
.byte $CB,$EA,0 ; SET 5,D
|
||||
.byte $CB,$EB,0 ; SET 5,E
|
||||
.byte $CB,$EC,0 ; SET 5,H
|
||||
.byte $CB,$ED,0 ; SET 5,L
|
||||
.byte $CB,$EF,0 ; SET 5,A
|
||||
|
||||
.byte $CB,$F0,0 ; SET 6,B
|
||||
.byte $CB,$F1,0 ; SET 6,C
|
||||
.byte $CB,$F2,0 ; SET 6,D
|
||||
.byte $CB,$F3,0 ; SET 6,E
|
||||
.byte $CB,$F4,0 ; SET 6,H
|
||||
.byte $CB,$F5,0 ; SET 6,L
|
||||
.byte $CB,$F7,0 ; SET 6,A
|
||||
|
||||
.byte $CB,$F8,0 ; SET 7,B
|
||||
.byte $CB,$F9,0 ; SET 7,C
|
||||
.byte $CB,$FA,0 ; SET 7,D
|
||||
.byte $CB,$FB,0 ; SET 7,E
|
||||
.byte $CB,$FC,0 ; SET 7,H
|
||||
.byte $CB,$FD,0 ; SET 7,L
|
||||
.byte $CB,$FF,0 ; SET 7,A
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
ld c,$00
|
||||
call test
|
||||
ld c,$F0
|
||||
call test
|
||||
ret
|
||||
|
||||
test:
|
||||
; Go through each value for A
|
||||
ld hl,values
|
||||
a_loop:
|
||||
ld b,(hl)
|
||||
push hl
|
||||
|
||||
; Go through each value for other registers
|
||||
ld hl,values
|
||||
values_loop:
|
||||
push bc
|
||||
push hl
|
||||
|
||||
push bc
|
||||
|
||||
; BC
|
||||
ld a,(hl+)
|
||||
ld b,a
|
||||
ld a,(hl+)
|
||||
ld c,a
|
||||
|
||||
; HL
|
||||
ld a,(hl+)
|
||||
ld d,a
|
||||
ld a,(hl+)
|
||||
ld e,a
|
||||
push de
|
||||
|
||||
; DE
|
||||
ld a,(hl+)
|
||||
ld d,a
|
||||
ld a,(hl+)
|
||||
ld e,a
|
||||
|
||||
pop hl
|
||||
pop af
|
||||
|
||||
; call print_regs
|
||||
jp instr
|
||||
instr_done:
|
||||
|
||||
; Checksum registers
|
||||
call checksum_af_bc_de_hl
|
||||
|
||||
pop hl
|
||||
pop bc
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,values_loop
|
||||
|
||||
pop hl
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,a_loop
|
||||
|
||||
ret
|
||||
|
||||
values:
|
||||
.byte $00,$01,$02,$04,$08,$10,$20,$40,$80,$FF
|
||||
values_end:
|
||||
.byte $00,$01,$02,$04,$08,$10,$20,$40,$80,$FF
|
||||
|
||||
checksums:
|
||||
.byte $46,$51,$4A,$16,$D4,$18,$B2,$4E,$ED,$B5,$15,$EA,$74,$66,$66,$3E
|
||||
.byte $C2,$F3,$7F,$6A,$63,$CA,$62,$21,$72,$1E,$E4,$83,$6A,$56,$41,$1D
|
||||
.byte $91,$90,$DB,$38,$54,$0A,$6C,$24,$02,$9E,$EA,$5B,$6D,$A7,$CB,$80
|
||||
.byte $B4,$0B,$F3,$0F,$40,$38,$75,$BB,$AF,$30,$2B,$E5,$BD,$97,$D0,$33
|
||||
.byte $83,$CB,$FD,$0A,$BB,$21,$93,$95,$28,$2F,$A2,$F6,$1B,$5F,$47,$E5
|
||||
.byte $A3,$2E,$39,$63,$6C,$E0,$02,$BB,$78,$F1,$BA,$CB,$2C,$9F,$49,$E0
|
||||
.byte $6C,$E0,$02,$BB,$04,$28,$A9,$FD,$5E,$D7,$2E,$93,$1B,$78,$08,$00
|
||||
.byte $83,$CB,$FD,$0A,$BB,$21,$93,$95,$69,$17,$20,$96,$C3,$B4,$B6,$51
|
||||
.byte $C1,$4E,$C3,$05,$72,$D0,$25,$98,$44,$F0,$99,$B7,$B4,$0B,$F3,$0F
|
||||
.byte $54,$0A,$6C,$24,$45,$10,$2B,$9D,$86,$3C,$DF,$27,$02,$9E,$EA,$5B
|
||||
.byte $B7,$B6,$4F,$60,$70,$E0,$E1,$AA,$C2,$F3,$7F,$6A,$63,$CA,$62,$21
|
||||
.byte $80,$76,$41,$65,$AA,$3B,$D4,$2C,$ED,$B5,$15,$EA,$74,$66,$66,$3E
|
||||
.byte $AD,$FF,$A0,$43,$7B,$4C,$06,$A4,$15,$32,$EE,$44,$43,$A6,$68,$3B
|
||||
.byte $6F,$5D,$BE,$D4,$DA,$75,$1B,$EF,$9B,$4D,$99,$8F,$49,$E8,$A9,$1D
|
||||
.byte $F5,$1B,$58,$3A,$92,$25,$2D,$51,$38,$5C,$62,$05,$DD,$A9,$63,$AD
|
||||
.byte $E3,$78,$2F,$37,$90,$15,$DB,$62,$58,$E2,$E8,$35,$BB,$C1,$5A,$EA
|
||||
.byte $06,$FE,$28,$AA,$4F,$5D,$64,$BF,$83,$CF,$7F,$B2,$F9,$A9,$90,$BF
|
||||
.byte $DD,$06,$B6,$64,$25,$8A,$E0,$24,$FA,$40,$95,$13,$91,$61,$93,$0D
|
||||
.byte $69,$A8,$0E,$0B,$AE,$FD,$DF,$1A,$D4,$98,$D8,$11,$61,$E9,$16,$66
|
||||
.byte $BD,$82,$1F,$2C,$E2,$74,$26,$77,$13,$E4,$6A,$25,$D7,$DE,$8A,$4F
|
||||
.byte $1F,$7B,$47,$BC,$DA,$DB,$31,$E7,$2B,$06,$2C,$39,$15,$FC,$1C,$0B
|
||||
.byte $1A,$3B,$A0,$0F,$55,$E5,$D8,$1C,$6D,$6C,$7F,$B8,$14,$AD,$9C,$AF
|
||||
.byte $92,$B6,$60,$40,$76,$E6,$6D,$2F,$9E,$CA,$45,$6D,$54,$97,$47,$35
|
||||
.byte $EE,$39,$50,$63,$47,$8C,$8A,$AB,$18,$F7,$6D,$10,$B7,$A6,$74,$0C
|
||||
.byte $11,$24,$9C,$F5,$64,$5D,$FB,$16,$65,$1C,$59,$C6,$B9,$E3,$30,$52
|
||||
.byte $1D,$E4,$B8,$9E,$A3,$2F,$7B,$6F,$03,$20,$24,$41,$4C,$F7,$22,$B8
|
||||
.byte $92,$A7,$75,$E3,$1D,$F2,$5E,$FD,$B7,$A4,$F3,$34,$BF,$F7,$37,$CA
|
||||
.byte $67,$22,$D4,$4D,$DE,$1A,$99,$58,$B2,$65,$91,$12,$F2,$8C,$65,$08
|
||||
.byte $69,$E2,$9B,$D3,$94,$8C,$71,$F1,$D8,$22,$29,$53,$E8,$6A,$D9,$55
|
||||
.byte $3E,$24,$42,$EF,$38,$12,$AC,$02,$35,$84,$7D,$2C,$C2,$34,$AC,$E2
|
||||
.byte $4B,$AA,$E0,$31,$8F,$A0,$F2,$13,$A8,$4F,$7B,$98,$02,$16,$3B,$D4
|
||||
.byte $8D,$09,$58,$A4,$FF,$46,$CA,$17,$08,$AA,$78,$02,$4A,$CF,$72,$E1
|
||||
.byte $A8,$55,$52,$89,$F8,$FD,$D6,$4E,$22,$E7,$8F,$C6,$80,$F1,$BB,$3C
|
||||
.byte $09,$1B,$4A,$4A,$06,$A1,$FD,$54,$E4,$BF,$D8,$27,$14,$23,$42,$90
|
||||
.byte $B3,$7B,$55,$14,$77,$22,$EE,$92,$E9,$37,$76,$8C,$7D,$CF,$B7,$C7
|
||||
.byte $D2,$90,$17,$48,$BB,$52,$BC,$19,$AA,$91,$9F,$DC,$0D,$AA,$C9,$24
|
||||
.byte $C8,$45,$DF,$AB,$B3,$83,$A8,$9E,$0F,$AA,$62,$2F,$C4,$C0,$28,$BA
|
||||
.byte $32,$56,$99,$69,$C9,$77,$4B,$62,$6B,$FF,$B6,$DD,$42,$46,$7A,$00
|
||||
.byte $DA,$E9,$67,$4D,$46,$9C,$B5,$92,$04,$B5,$F6,$03,$01,$3C,$A2,$47
|
||||
.byte $40,$15,$4A,$D6,$04,$39,$BC,$2F,$E9,$E1,$39,$59,$9B,$6A,$A4,$12
|
||||
.byte $97,$23,$99,$30,$9E,$A6,$70,$AD,$C7,$1B,$D6,$1F,$05,$15,$D2,$5B
|
||||
.byte $29,$0F,$5A,$CC,$0A,$99,$A2,$68,$5D,$58,$ED,$9C,$B9,$82,$CD,$74
|
||||
162
cpu_instrs/source/11-op a,(hl).s
Normal file
162
cpu_instrs/source/11-op a,(hl).s
Normal file
@@ -0,0 +1,162 @@
|
||||
; Tests (HL/BC/DE) instructions.
|
||||
; Takes 20 seconds.
|
||||
|
||||
;.define PRINT_CHECKSUMS 1
|
||||
.include "shell.inc"
|
||||
.include "instr_test.s"
|
||||
|
||||
instrs:
|
||||
.byte $0A,0,0 ; LD A,(BC)
|
||||
.byte $1A,0,0 ; LD A,(DE)
|
||||
.byte $02,0,0 ; LD (BC),A
|
||||
.byte $12,0,0 ; LD (DE),A
|
||||
.byte $2A,0,0 ; LD A,(HL+)
|
||||
.byte $3A,0,0 ; LD A,(HL-)
|
||||
.byte $22,0,0 ; LD (HL+),A
|
||||
.byte $32,0,0 ; LD (HL-),A
|
||||
.byte $B6,0,0 ; OR (HL)
|
||||
.byte $BE,0,0 ; CP (HL)
|
||||
.byte $86,0,0 ; ADD (HL)
|
||||
.byte $8E,0,0 ; ADC (HL)
|
||||
.byte $96,0,0 ; SUB (HL)
|
||||
.byte $9E,0,0 ; SBC (HL)
|
||||
.byte $A6,0,0 ; AND (HL)
|
||||
.byte $AE,0,0 ; XOR (HL)
|
||||
.byte $35,0,0 ; DEC (HL)
|
||||
.byte $34,0,0 ; INC (HL)
|
||||
.byte $CB,$06,0 ; RLC (HL)
|
||||
.byte $CB,$0E,0 ; RRC (HL)
|
||||
.byte $CB,$16,0 ; RL (HL)
|
||||
.byte $CB,$1E,0 ; RR (HL)
|
||||
.byte $CB,$26,0 ; SLA (HL)
|
||||
.byte $CB,$2E,0 ; SRA (HL)
|
||||
.byte $CB,$36,0 ; SWAP (HL)
|
||||
.byte $CB,$3E,0 ; SRL (HL)
|
||||
.byte $CB,$46,0 ; BIT 0,(HL)
|
||||
.byte $CB,$4E,0 ; BIT 1,(HL)
|
||||
.byte $CB,$56,0 ; BIT 2,(HL)
|
||||
.byte $CB,$5E,0 ; BIT 3,(HL)
|
||||
.byte $CB,$66,0 ; BIT 4,(HL)
|
||||
.byte $CB,$6E,0 ; BIT 5,(HL)
|
||||
.byte $CB,$76,0 ; BIT 6,(HL)
|
||||
.byte $CB,$7E,0 ; BIT 7,(HL)
|
||||
.byte $CB,$86,0 ; RES 0,(HL)
|
||||
.byte $CB,$8E,0 ; RES 1,(HL)
|
||||
.byte $CB,$96,0 ; RES 2,(HL)
|
||||
.byte $CB,$9E,0 ; RES 3,(HL)
|
||||
.byte $CB,$A6,0 ; RES 4,(HL)
|
||||
.byte $CB,$AE,0 ; RES 5,(HL)
|
||||
.byte $CB,$B6,0 ; RES 6,(HL)
|
||||
.byte $CB,$BE,0 ; RES 7,(HL)
|
||||
.byte $CB,$C6,0 ; SET 0,(HL)
|
||||
.byte $CB,$CE,0 ; SET 1,(HL)
|
||||
.byte $CB,$D6,0 ; SET 2,(HL)
|
||||
.byte $CB,$DE,0 ; SET 3,(HL)
|
||||
.byte $CB,$E6,0 ; SET 4,(HL)
|
||||
.byte $CB,$EE,0 ; SET 5,(HL)
|
||||
.byte $CB,$F6,0 ; SET 6,(HL)
|
||||
.byte $CB,$FE,0 ; SET 7,(HL)
|
||||
.byte $27,0,0 ; DAA
|
||||
instrs_end:
|
||||
|
||||
test_instr:
|
||||
ld c,$00
|
||||
call test
|
||||
ld c,$10
|
||||
call test
|
||||
ld c,$E0
|
||||
call test
|
||||
ld c,$F0
|
||||
call test
|
||||
ret
|
||||
|
||||
test:
|
||||
; Go through each value for A
|
||||
ld hl,values
|
||||
a_loop:
|
||||
ld b,(hl)
|
||||
push hl
|
||||
|
||||
; Go through each value for (HL)
|
||||
ld hl,values
|
||||
values_loop:
|
||||
push bc
|
||||
push hl
|
||||
|
||||
push bc
|
||||
|
||||
; BC
|
||||
ld a,(hl+)
|
||||
ld bc,rp_temp
|
||||
ld (rp_temp),a
|
||||
|
||||
; DE
|
||||
ld a,(hl+)
|
||||
ld de,rp_temp+1
|
||||
ld (rp_temp+1),a
|
||||
|
||||
; HL
|
||||
ld a,(hl)
|
||||
ld hl,rp_temp+2
|
||||
ld (rp_temp+2),a
|
||||
|
||||
; AF
|
||||
pop af
|
||||
|
||||
; call print_regs
|
||||
jp instr
|
||||
instr_done:
|
||||
|
||||
; Checksum AF, HL, and (HL)
|
||||
push hl
|
||||
push af
|
||||
call update_crc_fast
|
||||
pop hl
|
||||
ld a,l
|
||||
call update_crc_fast
|
||||
pop bc
|
||||
ld a,b
|
||||
call update_crc_fast
|
||||
ld a,c
|
||||
call update_crc_fast
|
||||
ld a,(rp_temp)
|
||||
call update_crc_fast
|
||||
ld a,(rp_temp+1)
|
||||
call update_crc_fast
|
||||
ld a,(rp_temp+2)
|
||||
call update_crc_fast
|
||||
|
||||
pop hl
|
||||
pop bc
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,values_loop
|
||||
|
||||
pop hl
|
||||
inc hl
|
||||
ld a,l
|
||||
cp <values_end
|
||||
jr nz,a_loop
|
||||
|
||||
ret
|
||||
|
||||
values:
|
||||
.byte $00,$01,$0F,$10,$1F,$7F,$80,$F0,$FF,$02,$04,$08,$20,$40
|
||||
values_end:
|
||||
.byte $00,$01,$0F,$10,$1F,$7F,$80,$F0,$FF,$02,$04,$08,$20,$40
|
||||
|
||||
checksums:
|
||||
.byte $E0,$E5,$09,$A7,$FB,$28,$0D,$AE,$AC,$BB,$91,$D8,$B3,$E2,$AF,$C4
|
||||
.byte $3D,$B5,$02,$07,$4F,$6E,$5B,$7E,$AE,$02,$E7,$14,$DC,$D9,$BE,$6D
|
||||
.byte $F1,$48,$A9,$42,$67,$08,$FE,$57,$06,$6A,$A9,$B1,$FD,$A5,$84,$F0
|
||||
.byte $82,$FC,$24,$A9,$A8,$1D,$BB,$E2,$F8,$23,$8C,$DE,$0E,$1D,$64,$D1
|
||||
.byte $05,$E0,$24,$41,$53,$75,$47,$55,$F4,$D9,$10,$6A,$38,$16,$28,$D8
|
||||
.byte $D1,$28,$A3,$E0,$A2,$05,$B8,$FE,$B0,$F4,$F5,$8F,$4B,$39,$03,$B0
|
||||
.byte $8A,$07,$BA,$90,$25,$99,$A7,$78,$E6,$9A,$D1,$49,$C9,$B2,$A3,$E5
|
||||
.byte $36,$34,$CB,$5A,$97,$42,$71,$09,$39,$87,$25,$EC,$54,$EE,$C5,$B3
|
||||
.byte $FC,$B5,$6F,$BD,$0B,$D8,$46,$6F,$6A,$27,$81,$9F,$F8,$38,$E2,$71
|
||||
.byte $55,$19,$21,$83,$4B,$85,$9F,$4B,$A1,$78,$14,$60,$58,$08,$D9,$57
|
||||
.byte $11,$8C,$83,$9A,$9F,$01,$D1,$90,$E8,$82,$0B,$5A,$BD,$75,$86,$21
|
||||
.byte $DF,$83,$E9,$23,$1E,$B6,$7F,$D1,$4A,$18,$A5,$8E,$CF,$CF,$CA,$51
|
||||
.byte $3F,$03,$A4,$96,$C3,$1F,$9E,$88,$0C,$DF,$1F,$B1
|
||||
215
cpu_instrs/source/common/apu.s
Normal file
215
cpu_instrs/source/common/apu.s
Normal file
@@ -0,0 +1,215 @@
|
||||
; Sound chip utilities
|
||||
|
||||
; Turns APU off
|
||||
; Preserved: BC, DE, HL
|
||||
sound_off:
|
||||
wreg NR52,0
|
||||
ret
|
||||
|
||||
|
||||
; Turns APU on
|
||||
; Preserved: BC, DE, HL
|
||||
sound_on:
|
||||
wreg NR52,$80 ; power
|
||||
wreg NR51,$FF ; mono
|
||||
wreg NR50,$77 ; volume
|
||||
ret
|
||||
|
||||
|
||||
; Synchronizes to APU length counter within
|
||||
; tens of clocks. Uses square 2 channel.
|
||||
; Preserved: BC, DE, HL
|
||||
sync_apu:
|
||||
wreg NR24,$00 ; disable length
|
||||
wreg NR21,$3E ; length = 2 (in case of extra len clk)
|
||||
wreg NR22,$08 ; silent without disabling channel
|
||||
wreg NR24,$C0 ; start length
|
||||
- lda NR52 ; wait for length to reach zero
|
||||
and $02
|
||||
jr nz,-
|
||||
ret
|
||||
|
||||
|
||||
; Synchronizes to first square sweep within
|
||||
; tens of clocks. Uses square 1 channel.
|
||||
; Preserved: BC, DE, HL
|
||||
sync_sweep:
|
||||
wreg NR10,$11 ; sweep period = 1, shift = 1
|
||||
wreg NR12,$08 ; silent without disabling channel
|
||||
wreg NR13,$FF ; freq = $3FF
|
||||
wreg NR14,$83 ; start
|
||||
- lda NR52
|
||||
and $01
|
||||
jr nz,-
|
||||
ret
|
||||
|
||||
|
||||
; Copies 16-byte wave from (HL) to wave RAM
|
||||
; Preserved: BC, DE
|
||||
load_wave:
|
||||
push bc
|
||||
wreg NR30,$00 ; disable while writing
|
||||
ld c,$30
|
||||
- ld a,(hl+)
|
||||
ld ($FF00+c),a
|
||||
inc c
|
||||
bit 6,c
|
||||
jr z,-
|
||||
pop bc
|
||||
ret
|
||||
|
||||
|
||||
; Makes short beep
|
||||
; Preserved: BC, DE, HL
|
||||
beep:
|
||||
xor a ; sound off
|
||||
sta NR52
|
||||
dec a
|
||||
sta NR52 ; sound on
|
||||
sta NR51 ; mono
|
||||
sta NR50 ; volume
|
||||
wreg NR12,$F1 ; volume, envelope rate
|
||||
wreg NR14,$86 ; note on, pitch
|
||||
delay_msec 250
|
||||
ret
|
||||
|
||||
|
||||
; Marks sound with bits of A encoded into volume
|
||||
; Preserved: BC, DE, HL
|
||||
mark_sound:
|
||||
push bc
|
||||
ld c,a
|
||||
ld b,8
|
||||
wreg NR10,0
|
||||
wreg NR11,$80
|
||||
wreg NR13,$F8
|
||||
- ld a,$60
|
||||
rl c
|
||||
jr nc,+
|
||||
ld a,$A0
|
||||
+ sta NR12
|
||||
wreg NR14,$87
|
||||
delay_usec 300
|
||||
wreg NR12,0
|
||||
delay_usec 100
|
||||
dec b
|
||||
jr nz,-
|
||||
pop bc
|
||||
ret
|
||||
|
||||
|
||||
; Fills wave RAM with A
|
||||
; Preserved: BC, DE, HL
|
||||
fill_wave:
|
||||
push bc
|
||||
ld c,$30
|
||||
- ld ($FF00+c),a
|
||||
inc c
|
||||
bit 6,c
|
||||
jr z,-
|
||||
pop bc
|
||||
ret
|
||||
|
||||
|
||||
; Gets current length counter value for
|
||||
; channel with mask A into A. Length counter
|
||||
; must be enabled for that channel.
|
||||
; Preserved: BC, DE, HL
|
||||
get_len_a:
|
||||
push bc
|
||||
ld c,a
|
||||
ld b,0
|
||||
- lda NR52 ; 3
|
||||
and c ; 1
|
||||
jr z,+ ; 2
|
||||
delay 4096-10
|
||||
inc b ; 1
|
||||
jr nz,- ; 3
|
||||
+ ld a,b
|
||||
pop bc
|
||||
ret
|
||||
|
||||
|
||||
; Synchronizes exactly to length clock. Next length clock
|
||||
; occurs by 4079 clocks after this returns. Uses NR2x.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
sync_length:
|
||||
push af
|
||||
push hl
|
||||
|
||||
ld hl,NR52
|
||||
wreg NR22,$08 ; silent without disabling channel
|
||||
wreg NR24,$40 ; avoids extra length clock on trigger
|
||||
wreg NR21,-2 ; length = 2, in case clock occurs immediately
|
||||
wreg NR24,$C0 ; start length
|
||||
|
||||
; Coarse sync
|
||||
ld a,$02
|
||||
- and (hl)
|
||||
jr nz,-
|
||||
|
||||
; Fine sync. Slowly moves "forward" until
|
||||
; length clock occurs just before reading NR52.
|
||||
- delay 4097-20
|
||||
wreg NR21,-1 ; 5
|
||||
wreg NR24,$C0 ; 5
|
||||
lda NR52 ; 3
|
||||
delay 2 ; 2
|
||||
and $02 ; 2
|
||||
jr nz,- ; 3
|
||||
|
||||
pop hl
|
||||
pop af
|
||||
ret
|
||||
|
||||
|
||||
; Delays n*4096 cycles
|
||||
; Preserved: BC, DE, HL
|
||||
.macro delay_frames ; n
|
||||
ld a,\1
|
||||
call delay_frames_
|
||||
.endm
|
||||
|
||||
|
||||
; Delays A*4096+13 cycles (including CALL)
|
||||
; Preserved: BC, DE, HL
|
||||
delay_a_frames:
|
||||
or a ; 1
|
||||
jr nz,+ ; 3
|
||||
; -1
|
||||
ret
|
||||
delay_frames_: ; delays 4096*A-2 cycles (including CALL)
|
||||
push af ; 4
|
||||
ld a,256-13-20-12 ; 2
|
||||
jr ++ ; 3
|
||||
+
|
||||
- push af ; 4
|
||||
ld a,256-13-20 ; 2
|
||||
++ call delay_a_20_cycles
|
||||
delay 4096-256
|
||||
pop af ; 3
|
||||
dec a ; 1
|
||||
jr nz,- ; 3
|
||||
; -1
|
||||
ret
|
||||
|
||||
|
||||
.macro test_chan_timing ; chan, iter
|
||||
ld a,\1
|
||||
call print_dec
|
||||
call print_space
|
||||
ld a,\2
|
||||
- push af
|
||||
test_chan 1<<\1, \1*5+NR10
|
||||
pop af
|
||||
dec a
|
||||
jr nz,-
|
||||
call print_newline
|
||||
.endm
|
||||
|
||||
.macro test_chans ARGS iter
|
||||
test_chan_timing 0,iter
|
||||
test_chan_timing 1,iter
|
||||
test_chan_timing 2,iter
|
||||
test_chan_timing 3,iter
|
||||
.endm
|
||||
121
cpu_instrs/source/common/build_gbs.s
Normal file
121
cpu_instrs/source/common/build_gbs.s
Normal file
@@ -0,0 +1,121 @@
|
||||
; Build as GBS music file
|
||||
|
||||
.memoryMap
|
||||
defaultSlot 0
|
||||
slot 0 $3000 size $1000
|
||||
slot 1 $C000 size $1000
|
||||
.endMe
|
||||
|
||||
.romBankSize $1000
|
||||
.romBanks 2
|
||||
|
||||
|
||||
;;;; GBS music file header
|
||||
|
||||
.byte "GBS"
|
||||
.byte 1 ; vers
|
||||
.byte 1 ; songs
|
||||
.byte 1 ; first song
|
||||
.word load_addr
|
||||
.word reset
|
||||
.word gbs_play
|
||||
.word std_stack
|
||||
.byte 0,0 ; timer
|
||||
.ds $60,0
|
||||
load_addr:
|
||||
|
||||
; WLA assumes we're building ROM and messes
|
||||
; with bytes at the beginning, so skip them.
|
||||
.ds $100,0
|
||||
|
||||
|
||||
;;;; Shell
|
||||
|
||||
.include "runtime.s"
|
||||
|
||||
init_runtime:
|
||||
ld a,$01 ; Identify as DMG hardware
|
||||
ld (gb_id),a
|
||||
.ifdef TEST_NAME
|
||||
print_str TEST_NAME,newline,newline
|
||||
.endif
|
||||
ret
|
||||
|
||||
std_print:
|
||||
sta SB
|
||||
wreg SC,$81
|
||||
delay 2304
|
||||
ret
|
||||
|
||||
post_exit:
|
||||
call play_byte
|
||||
forever:
|
||||
wreg NR52,0 ; sound off
|
||||
- jp -
|
||||
|
||||
.ifndef CUSTOM_RESET
|
||||
gbs_play:
|
||||
.endif
|
||||
console_flush:
|
||||
console_normal:
|
||||
console_inverse:
|
||||
console_set_mode:
|
||||
ret
|
||||
|
||||
; Reports A in binary as high and low tones, with
|
||||
; leading low tone for reference. Omits leading
|
||||
; zeroes.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
play_byte:
|
||||
push af
|
||||
push hl
|
||||
|
||||
; HL = (A << 1) | 1
|
||||
scf
|
||||
rla
|
||||
ld l,a
|
||||
ld h,0
|
||||
rl h
|
||||
|
||||
; Shift left until next-to-top bit is 1
|
||||
- add hl,hl
|
||||
bit 6,h
|
||||
jr z,-
|
||||
|
||||
; Reset sound
|
||||
delay_msec 400
|
||||
wreg NR52,0 ; sound off
|
||||
wreg NR52,$80 ; sound on
|
||||
wreg NR51,$FF ; mono
|
||||
wreg NR50,$77 ; volume
|
||||
|
||||
- add hl,hl
|
||||
|
||||
; Low or high pitch based on bit shifted out
|
||||
; of HL
|
||||
ld a,0
|
||||
jr nc,+
|
||||
ld a,$FF
|
||||
+ sta NR23
|
||||
|
||||
; Play short tone
|
||||
wreg NR21,$A0
|
||||
wreg NR22,$F0
|
||||
wreg NR24,$86
|
||||
delay_msec 75
|
||||
wreg NR22,0
|
||||
wreg NR23,$F8
|
||||
wreg NR24,$87
|
||||
delay_msec 200
|
||||
|
||||
; Loop until HL = $8000
|
||||
ld a,h
|
||||
xor $80
|
||||
or l
|
||||
jr nz,-
|
||||
|
||||
pop hl
|
||||
pop af
|
||||
ret
|
||||
|
||||
.ends
|
||||
80
cpu_instrs/source/common/build_rom.s
Normal file
80
cpu_instrs/source/common/build_rom.s
Normal file
@@ -0,0 +1,80 @@
|
||||
; Build as GB ROM
|
||||
|
||||
.memoryMap
|
||||
defaultSlot 0
|
||||
slot 0 $0000 size $4000
|
||||
slot 1 $C000 size $4000
|
||||
.endMe
|
||||
|
||||
.romBankSize $4000 ; generates $8000 byte ROM
|
||||
.romBanks 2
|
||||
|
||||
.cartridgeType 1 ; MBC1
|
||||
.computeChecksum
|
||||
.computeComplementCheck
|
||||
|
||||
|
||||
;;;; GB ROM header
|
||||
|
||||
; GB header read by bootrom
|
||||
.org $100
|
||||
nop
|
||||
jp reset
|
||||
|
||||
; Nintendo logo required for proper boot
|
||||
.byte $CE,$ED,$66,$66,$CC,$0D,$00,$0B
|
||||
.byte $03,$73,$00,$83,$00,$0C,$00,$0D
|
||||
.byte $00,$08,$11,$1F,$88,$89,$00,$0E
|
||||
.byte $DC,$CC,$6E,$E6,$DD,$DD,$D9,$99
|
||||
.byte $BB,$BB,$67,$63,$6E,$0E,$EC,$CC
|
||||
.byte $DD,$DC,$99,$9F,$BB,$B9,$33,$3E
|
||||
|
||||
; Internal name
|
||||
.ifdef ROM_NAME
|
||||
.byte ROM_NAME
|
||||
.endif
|
||||
|
||||
; CGB/DMG requirements
|
||||
.org $143
|
||||
.ifdef REQUIRE_CGB
|
||||
.byte $C0
|
||||
.else
|
||||
.ifndef REQUIRE_DMG
|
||||
.byte $80
|
||||
.endif
|
||||
.endif
|
||||
|
||||
.org $200
|
||||
|
||||
|
||||
;;;; Shell
|
||||
|
||||
.include "runtime.s"
|
||||
.include "console.s"
|
||||
|
||||
init_runtime:
|
||||
call console_init
|
||||
.ifdef TEST_NAME
|
||||
print_str TEST_NAME,newline,newline
|
||||
.endif
|
||||
ret
|
||||
|
||||
std_print:
|
||||
push af
|
||||
sta SB
|
||||
wreg SC,$81
|
||||
delay 2304
|
||||
pop af
|
||||
jp console_print
|
||||
|
||||
post_exit:
|
||||
call console_show
|
||||
call play_byte
|
||||
forever:
|
||||
wreg NR52,0 ; sound off
|
||||
- jr -
|
||||
|
||||
play_byte:
|
||||
ret
|
||||
|
||||
.ends
|
||||
98
cpu_instrs/source/common/checksums.s
Normal file
98
cpu_instrs/source/common/checksums.s
Normal file
@@ -0,0 +1,98 @@
|
||||
; Multiple checksum table handling
|
||||
|
||||
.define next_checksum bss+0
|
||||
.redefine bss bss+2
|
||||
|
||||
; If PRINT_CHECKSUMS is defined, checksums are printed
|
||||
; rather than compared.
|
||||
|
||||
; Initializes multiple checksum handler to use checksums
|
||||
; table (defined by user).
|
||||
; Preserved: BC, DE, HL
|
||||
checksums_init:
|
||||
ld a,<checksums
|
||||
ld (next_checksum),a
|
||||
ld a,>checksums
|
||||
ld (next_checksum+1),a
|
||||
ret
|
||||
|
||||
; Compares current checksum with next checksum in
|
||||
; list. Z if they match, NZ if not.
|
||||
; Preserved: BC, DE, HL
|
||||
checksums_compare:
|
||||
.ifdef PRINT_CHECKSUMS
|
||||
lda checksum+3
|
||||
push af
|
||||
lda checksum+2
|
||||
push af
|
||||
lda checksum+1
|
||||
push af
|
||||
lda checksum+0
|
||||
push af
|
||||
|
||||
ld a,(next_checksum)
|
||||
inc a
|
||||
ld (next_checksum),a
|
||||
sub <checksums+1
|
||||
and $03
|
||||
ld a,','
|
||||
jr nz,+
|
||||
print_str newline,'.',"byte"
|
||||
ld a,' '
|
||||
+ call print_char
|
||||
|
||||
pop af
|
||||
call @print_byte
|
||||
pop af
|
||||
call @print_byte
|
||||
pop af
|
||||
call @print_byte
|
||||
ld a,'$'
|
||||
call print_char
|
||||
pop af
|
||||
call print_hex
|
||||
|
||||
xor a
|
||||
ret
|
||||
|
||||
@print_byte:
|
||||
push af
|
||||
ld a,'$'
|
||||
call print_char
|
||||
pop af
|
||||
call print_hex
|
||||
ld a,','
|
||||
call print_char
|
||||
ret
|
||||
.else
|
||||
|
||||
push bc
|
||||
push de
|
||||
push hl
|
||||
ld a,(next_checksum)
|
||||
ld l,a
|
||||
ld a,(next_checksum+1)
|
||||
ld h,a
|
||||
ld de,checksum
|
||||
ld b,0
|
||||
- ld a,(de)
|
||||
xor (hl)
|
||||
or b
|
||||
ld b,a
|
||||
inc hl
|
||||
inc e
|
||||
ld a,e
|
||||
cp <(checksum+4)
|
||||
jr nz,-
|
||||
ld a,l
|
||||
ld (next_checksum),a
|
||||
ld a,h
|
||||
ld (next_checksum+1),a
|
||||
|
||||
ld a,b
|
||||
cp 0
|
||||
pop hl
|
||||
pop de
|
||||
pop bc
|
||||
ret
|
||||
.endif
|
||||
BIN
cpu_instrs/source/common/console.bin
Normal file
BIN
cpu_instrs/source/common/console.bin
Normal file
Binary file not shown.
291
cpu_instrs/source/common/console.s
Normal file
291
cpu_instrs/source/common/console.s
Normal file
@@ -0,0 +1,291 @@
|
||||
; Scrolling text console
|
||||
|
||||
; Console is 20x18 characters. Buffers lines, so
|
||||
; output doesn't appear until a newline or flush.
|
||||
; If scrolling isn't supported (i.e. SCY is treated
|
||||
; as if always zero), the first 18 lines will
|
||||
; still print properly). Also works properly if
|
||||
; LY isn't supported (always reads back as the same
|
||||
; value).
|
||||
|
||||
.define console_width 20
|
||||
|
||||
.define console_buf bss+0
|
||||
.define console_pos bss+console_width
|
||||
.define console_mode bss+console_width+1
|
||||
.define console_scroll bss+console_width+2
|
||||
.redefine bss bss+console_width+3
|
||||
|
||||
|
||||
; Waits for start of LCD blanking period
|
||||
; Preserved: BC, DE, HL
|
||||
console_wait_vbl:
|
||||
push bc
|
||||
|
||||
; Wait for start of vblank, with
|
||||
; timeout in case LY doesn't work
|
||||
; or LCD is disabled.
|
||||
ld bc,-1250
|
||||
- inc bc
|
||||
ld a,b
|
||||
or c
|
||||
jr z,@timeout
|
||||
lda LY
|
||||
cp 144
|
||||
jr nz,-
|
||||
@timeout:
|
||||
|
||||
pop bc
|
||||
ret
|
||||
|
||||
|
||||
; Initializes text console
|
||||
console_init:
|
||||
call console_hide
|
||||
|
||||
; CGB-specific inits
|
||||
ld a,(gb_id)
|
||||
and gb_id_cgb
|
||||
call nz,@init_cgb
|
||||
|
||||
; Clear nametable
|
||||
ld a,' '
|
||||
call @fill_nametable
|
||||
|
||||
; Load tiles
|
||||
ld hl,TILES+$200
|
||||
ld c,0
|
||||
call @load_tiles
|
||||
ld hl,TILES+$A00
|
||||
ld c,$FF
|
||||
call @load_tiles
|
||||
|
||||
; Init state
|
||||
ld a,console_width
|
||||
ld (console_pos),a
|
||||
ld a,0
|
||||
ld (console_mode),a
|
||||
ld a,-8
|
||||
ld (console_scroll),a
|
||||
call console_scroll_up_
|
||||
jr console_show
|
||||
|
||||
@fill_nametable:
|
||||
ld hl,BGMAP0
|
||||
ld b,4
|
||||
- ld (hl),a
|
||||
inc l
|
||||
jr nz,-
|
||||
inc h
|
||||
dec b
|
||||
jr nz,-
|
||||
ret
|
||||
|
||||
@init_cgb:
|
||||
; Clear palette
|
||||
wreg $FF68,$80
|
||||
ld b,16
|
||||
- wreg $FF69,$FF
|
||||
wreg $FF69,$7F
|
||||
wreg $FF69,$00
|
||||
wreg $FF69,$00
|
||||
wreg $FF69,$00
|
||||
wreg $FF69,$00
|
||||
wreg $FF69,$00
|
||||
wreg $FF69,$00
|
||||
dec b
|
||||
jr nz,-
|
||||
|
||||
; Clear attributes
|
||||
ld a,1
|
||||
ld (VBK),a
|
||||
ld a,0
|
||||
call @fill_nametable
|
||||
|
||||
ld a,0
|
||||
ld (VBK),a
|
||||
ret
|
||||
|
||||
@load_tiles:
|
||||
ld de,ASCII
|
||||
ld b,96
|
||||
-- push bc
|
||||
ld b,8
|
||||
- ld a,(de)
|
||||
inc de
|
||||
xor c
|
||||
ldi (hl),a
|
||||
ldi (hl),a
|
||||
dec b
|
||||
jr nz,-
|
||||
pop bc
|
||||
dec b
|
||||
jr nz,--
|
||||
ret
|
||||
|
||||
|
||||
; Shows console display
|
||||
; Preserved: AF, BC, DE, HL
|
||||
console_show:
|
||||
push af
|
||||
|
||||
; Enable LCD
|
||||
call console_wait_vbl
|
||||
wreg LCDC,$91
|
||||
wreg SCX,0
|
||||
wreg BGP,$E4
|
||||
|
||||
jp console_apply_scroll_
|
||||
|
||||
|
||||
; Hides console display by turning LCD off
|
||||
; Preserved: AF, BC, DE, HL
|
||||
console_hide:
|
||||
push af
|
||||
|
||||
; LCD off
|
||||
call console_wait_vbl
|
||||
wreg LCDC,$11
|
||||
|
||||
pop af
|
||||
ret
|
||||
|
||||
|
||||
; Changes to normal text mode
|
||||
; Preserved: BC, DE, HL
|
||||
console_normal:
|
||||
xor a
|
||||
jr console_set_mode
|
||||
|
||||
; Changes to inverse text mode
|
||||
; Preserved: BC, DE, HL
|
||||
console_inverse:
|
||||
ld a,$80
|
||||
|
||||
; Changes console mode to A.
|
||||
; 0: Normal, $80: Inverse
|
||||
; Preserved: BC, DE, HL
|
||||
console_set_mode:
|
||||
and $80
|
||||
ld (console_mode),a
|
||||
ret
|
||||
|
||||
|
||||
; Prints char A to console. Will not appear until
|
||||
; a newline or flush occurs.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
console_print:
|
||||
push af
|
||||
|
||||
cp 10
|
||||
jr z,console_newline_
|
||||
|
||||
push hl
|
||||
push af
|
||||
ld hl,console_pos
|
||||
ldi a,(hl)
|
||||
cp <console_buf
|
||||
jr nz,@not_at_end
|
||||
|
||||
; Newline if at end of current line. If this
|
||||
; were done after writing to buffer, calling
|
||||
; console_newline would print extra newline.
|
||||
; Doing it before eliminates this.
|
||||
|
||||
; Ignore any spaces at end of line
|
||||
pop af
|
||||
cp ' '
|
||||
jr z,@ignore_space
|
||||
call console_newline
|
||||
push af
|
||||
|
||||
@not_at_end:
|
||||
pop af
|
||||
or (hl) ; apply current attributes
|
||||
dec l ; hl = console_pos
|
||||
dec (hl) ; console_pos = console_pos - 1
|
||||
ld l,(hl) ; hl = position in buffer
|
||||
ld (hl),a
|
||||
|
||||
@ignore_space
|
||||
pop hl
|
||||
pop af
|
||||
ret
|
||||
|
||||
|
||||
; Displays current line and starts new one
|
||||
; Preserved: AF, BC, DE, HL
|
||||
console_newline:
|
||||
push af
|
||||
console_newline_:
|
||||
call console_wait_vbl
|
||||
call console_flush_
|
||||
call console_scroll_up_
|
||||
call console_flush_
|
||||
jp console_apply_scroll_
|
||||
|
||||
|
||||
console_scroll_up_:
|
||||
push bc
|
||||
push hl
|
||||
|
||||
; Scroll up 8 pixels
|
||||
ld a,(console_scroll)
|
||||
add 8
|
||||
ld (console_scroll),a
|
||||
|
||||
; Start new clear line
|
||||
ld a,' '
|
||||
ld hl,console_buf + console_width - 1
|
||||
ld b,console_width
|
||||
- ldd (hl),a
|
||||
dec b
|
||||
jr nz,-
|
||||
ld a,<(console_buf + console_width)
|
||||
ld (console_pos),a
|
||||
|
||||
pop hl
|
||||
pop bc
|
||||
ret
|
||||
|
||||
|
||||
; Displays current line's contents without scrolling.
|
||||
; Preserved: A, BC, DE, HL
|
||||
console_flush:
|
||||
push af
|
||||
call console_wait_vbl
|
||||
call console_flush_
|
||||
console_apply_scroll_:
|
||||
ld a,(console_scroll)
|
||||
sub 136
|
||||
sta SCY
|
||||
pop af
|
||||
ret
|
||||
|
||||
console_flush_:
|
||||
push de
|
||||
push hl
|
||||
|
||||
; Address of row in nametable
|
||||
ld a,(console_scroll)
|
||||
ld l,a
|
||||
ld h,(>BGMAP0) >> 2
|
||||
add hl,hl
|
||||
add hl,hl
|
||||
|
||||
; Copy line
|
||||
ld de,console_buf + console_width
|
||||
- dec e
|
||||
ld a,(de)
|
||||
ldi (hl),a
|
||||
ld a,e
|
||||
cp <console_buf
|
||||
jr nz,-
|
||||
|
||||
pop hl
|
||||
pop de
|
||||
ret
|
||||
|
||||
|
||||
ASCII:
|
||||
.incbin "console.bin"
|
||||
64
cpu_instrs/source/common/cpu_speed.s
Normal file
64
cpu_instrs/source/common/cpu_speed.s
Normal file
@@ -0,0 +1,64 @@
|
||||
; CPU speed manipulation.
|
||||
|
||||
; Switches to normal speed. No effect on DMG.
|
||||
; Preserved: BC, DE, HL
|
||||
cpu_norm:
|
||||
; Do nothing if not CGB
|
||||
ld a,(gb_id)
|
||||
and gb_id_cgb
|
||||
ret z
|
||||
|
||||
lda KEY1
|
||||
rlca
|
||||
ret nc
|
||||
jr cpu_speed_toggle
|
||||
|
||||
|
||||
; Switches to double speed. No effect on DMG.
|
||||
; Preserved: BC, DE, HL
|
||||
cpu_fast:
|
||||
; Do nothing if not CGB
|
||||
ld a,(gb_id)
|
||||
and gb_id_cgb
|
||||
ret z
|
||||
|
||||
lda KEY1
|
||||
rlca
|
||||
ret c
|
||||
cpu_speed_toggle:
|
||||
di
|
||||
lda IE
|
||||
push af
|
||||
xor a
|
||||
sta IE
|
||||
sta IF
|
||||
wreg P1,$30
|
||||
wreg KEY1,1
|
||||
stop
|
||||
nop
|
||||
pop af
|
||||
sta IE
|
||||
ret
|
||||
|
||||
|
||||
; Determines current CPU speed without using KEY1.
|
||||
; A=1 if fast, 0 if normal. Always 0 on DMG.
|
||||
; Preserved: BC, DE,HL
|
||||
get_cpu_speed:
|
||||
push bc
|
||||
call sync_apu
|
||||
wreg NR14,$C0
|
||||
wreg NR11,-1
|
||||
wreg NR12,8
|
||||
wreg NR14,$C0
|
||||
ld bc,-$262
|
||||
- inc bc
|
||||
lda NR52
|
||||
and 1
|
||||
jr nz,-
|
||||
ld a,0
|
||||
bit 7,b
|
||||
jr nz,+
|
||||
inc a
|
||||
+ pop bc
|
||||
ret
|
||||
78
cpu_instrs/source/common/crc.s
Normal file
78
cpu_instrs/source/common/crc.s
Normal file
@@ -0,0 +1,78 @@
|
||||
; CRC-32 checksum calculation
|
||||
|
||||
.define checksum dp+0 ; little-endian, complemented
|
||||
.redefine dp dp+4
|
||||
|
||||
|
||||
; Initializes checksum module. Might initialize tables
|
||||
; in the future.
|
||||
init_crc:
|
||||
jr reset_crc
|
||||
|
||||
|
||||
; Clears CRC
|
||||
; Preserved: BC, DE, HL
|
||||
reset_crc:
|
||||
ld a,$FF
|
||||
sta checksum+0
|
||||
sta checksum+1
|
||||
sta checksum+2
|
||||
sta checksum+3
|
||||
ret
|
||||
|
||||
|
||||
; Updates current checksum with byte A
|
||||
; Preserved: AF, BC, DE, HL
|
||||
; Time: 237 cycles average
|
||||
update_crc:
|
||||
; 65 cycles + 8*cycles per bit
|
||||
; min cycles per bit: 14
|
||||
; max cycles per bit: 29
|
||||
push af
|
||||
push bc
|
||||
push de
|
||||
push hl
|
||||
|
||||
ld hl,checksum+3
|
||||
ld b,(hl)
|
||||
dec l
|
||||
ld c,(hl)
|
||||
dec l
|
||||
ld d,(hl)
|
||||
dec l
|
||||
xor (hl)
|
||||
|
||||
ld h,8
|
||||
- srl b
|
||||
rr c
|
||||
rr d
|
||||
rra
|
||||
jr nc,+
|
||||
ld e,a
|
||||
ld a,b
|
||||
xor $ED
|
||||
ld b,a
|
||||
ld a,c
|
||||
xor $B8
|
||||
ld c,a
|
||||
ld a,d
|
||||
xor $83
|
||||
ld d,a
|
||||
ld a,e
|
||||
xor $20
|
||||
+ dec h
|
||||
jr nz,-
|
||||
|
||||
ld h,>checksum
|
||||
ldi (hl),a
|
||||
ld (hl),d
|
||||
inc l
|
||||
ld (hl),c
|
||||
inc l
|
||||
ld (hl),b
|
||||
|
||||
pop hl
|
||||
pop de
|
||||
pop bc
|
||||
pop af
|
||||
ret
|
||||
88
cpu_instrs/source/common/crc_fast.s
Normal file
88
cpu_instrs/source/common/crc_fast.s
Normal file
@@ -0,0 +1,88 @@
|
||||
; Fast table-based CRC-32
|
||||
|
||||
.define crc_tables (bss+$FF)&$FF00 ; 256-byte aligned
|
||||
.redefine bss crc_tables+$400
|
||||
|
||||
|
||||
; Initializes fast CRC tables and resets checksum.
|
||||
; Time: 47 msec
|
||||
init_crc_fast:
|
||||
ld l,0
|
||||
@next:
|
||||
xor a
|
||||
ld c,a
|
||||
ld d,a
|
||||
ld e,l
|
||||
|
||||
ld h,8
|
||||
- rra
|
||||
rr c
|
||||
rr d
|
||||
rr e
|
||||
jr nc,+
|
||||
xor $ED
|
||||
ld b,a
|
||||
ld a,c
|
||||
xor $B8
|
||||
ld c,a
|
||||
ld a,d
|
||||
xor $83
|
||||
ld d,a
|
||||
ld a,e
|
||||
xor $20
|
||||
ld e,a
|
||||
ld a,b
|
||||
|
||||
+ dec h
|
||||
jr nz,-
|
||||
|
||||
ld h,>crc_tables
|
||||
ld (hl),e
|
||||
inc h
|
||||
ld (hl),d
|
||||
inc h
|
||||
ld (hl),c
|
||||
inc h
|
||||
ld (hl),a
|
||||
|
||||
inc l
|
||||
jr nz,@next
|
||||
|
||||
jp init_crc
|
||||
|
||||
|
||||
; Faster version of update_crc
|
||||
; Preserved: BC, DE
|
||||
; Time: 50 cycles (including CALL)
|
||||
update_crc_fast:
|
||||
|
||||
; Fastest inline macro version of update_crc_fast
|
||||
; Time: 40 cycles
|
||||
; Size: 28 bytes
|
||||
.macro update_crc_fast
|
||||
ld l,a ; 1
|
||||
lda checksum ; 3
|
||||
xor l ; 1
|
||||
ld l,a ; 1
|
||||
ld h,>crc_tables ; 2
|
||||
|
||||
lda checksum+1 ; 3
|
||||
xor (hl) ; 2
|
||||
inc h ; 1
|
||||
sta checksum ; 3
|
||||
|
||||
lda checksum+2 ; 3
|
||||
xor (hl) ; 2
|
||||
inc h ; 1
|
||||
sta checksum+1 ; 3
|
||||
|
||||
lda checksum+3 ; 3
|
||||
xor (hl) ; 2
|
||||
inc h ; 1
|
||||
sta checksum+2 ; 3
|
||||
|
||||
ld a,(hl) ; 2
|
||||
sta checksum+3 ; 3
|
||||
.endm
|
||||
update_crc_fast
|
||||
ret
|
||||
220
cpu_instrs/source/common/delay.s
Normal file
220
cpu_instrs/source/common/delay.s
Normal file
@@ -0,0 +1,220 @@
|
||||
; Delays in cycles, milliseconds, etc.
|
||||
|
||||
; All routines are re-entrant (no global data). Routines never
|
||||
; touch BC, DE, or HL registers. These ASSUME CPU is at normal
|
||||
; speed. If running at double speed, msec/usec delays are half advertised.
|
||||
|
||||
; Delays n cycles, from 0 to 16777215
|
||||
; Preserved: AF, BC, DE, HL
|
||||
.macro delay ARGS n
|
||||
.if n < 0
|
||||
.printt "Delay must be >= 0"
|
||||
.fail
|
||||
.endif
|
||||
.if n > 16777215
|
||||
.printt "Delay must be < 16777216"
|
||||
.fail
|
||||
.endif
|
||||
delay_ n&$FFFF, n>>16
|
||||
.endm
|
||||
|
||||
; Delays n clocks, from 0 to 16777216*4. Must be multiple of 4.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
.macro delay_clocks ARGS n
|
||||
.if n # 4 != 0
|
||||
.printt "Delay must be a multiple of 4"
|
||||
.fail
|
||||
.endif
|
||||
delay_ (n/4)&$FFFF,(n/4)>>16
|
||||
.endm
|
||||
|
||||
; Delays n microseconds (1/1000000 second)
|
||||
; n can range from 0 to 4000 usec.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
.macro delay_usec ARGS n
|
||||
.if n < 0
|
||||
.printt "Delay must be >= 0"
|
||||
.fail
|
||||
.endif
|
||||
.if n > 4000
|
||||
.printt "Delay must be <= 4000 usec"
|
||||
.fail
|
||||
.endif
|
||||
delay_ ((n * 1048576 + 500000) / 1000000)&$FFFF,((n * 1048576 + 500000) / 1000000)>>16
|
||||
.endm
|
||||
|
||||
; Delays n milliseconds (1/1000 second)
|
||||
; n can range from 0 to 10000 msec.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
.macro delay_msec ARGS n
|
||||
.if n < 0
|
||||
.printt "Delay must be >= 0"
|
||||
.fail
|
||||
.endif
|
||||
.if n > 10000
|
||||
.printt "Delay must be <= 10000 msec"
|
||||
.fail
|
||||
.endif
|
||||
delay_ ((n * 1048576 + 500) / 1000)&$FFFF, ((n * 1048576 + 500) / 1000)>>16
|
||||
.endm
|
||||
|
||||
; All the low/high quantities are to deal wla-dx's asinine
|
||||
; restriction full expressions must evaluate to a 16-bit
|
||||
; value. If the author ever rectifies this, all "high"
|
||||
; arguments can be treated as zero and removed. Better yet,
|
||||
; I'll just find an assembler that didn't crawl out of
|
||||
; the sewer (this is one of too many bugs I've wasted
|
||||
; hours working around).
|
||||
|
||||
.define max_short_delay 28
|
||||
|
||||
.macro delay_long_ ARGS n, high
|
||||
; 0+ to avoid assembler treating as memory read
|
||||
ld a,0+(((high<<16)+n) - 11) >> 16
|
||||
call delay_65536a_9_cycles_
|
||||
delay_nosave_ (((high<<16)+n) - 11)&$FFFF, 0
|
||||
.endm
|
||||
|
||||
; Doesn't save AF, allowing minimization of AF save/restore
|
||||
.macro delay_nosave_ ARGS n, high
|
||||
; 65536+11 = maximum delay using delay_256a_9_cycles_
|
||||
; 255+22 = maximum delay using delay_a_20_cycles
|
||||
; 22 = minimum delay using delay_a_20_cycles
|
||||
.if high > 1
|
||||
delay_long_ n, high
|
||||
.else
|
||||
.if high*n > 11
|
||||
delay_long_ n, high
|
||||
.else
|
||||
.if (high*(255+22+1))|n > 255+22
|
||||
ld a,>(((high<<16)+n) - 11)
|
||||
call delay_256a_9_cycles_
|
||||
delay_nosave_ <(((high<<16)+n) - 11), 0
|
||||
.else
|
||||
.if n >= 22
|
||||
ld a,n - 22
|
||||
call delay_a_20_cycles
|
||||
.else
|
||||
delay_short_ n
|
||||
.endif
|
||||
.endif
|
||||
.endif
|
||||
.endif
|
||||
.endm
|
||||
|
||||
.macro delay_ ARGS low, high
|
||||
.if (high*(max_short_delay+1))|low > max_short_delay
|
||||
push af
|
||||
delay_nosave_ ((high<<16)+low - 7)&$FFFF, ((high<<16)+low - 7)>>16
|
||||
pop af
|
||||
.else
|
||||
delay_short_ low
|
||||
.endif
|
||||
.endm
|
||||
|
||||
|
||||
; Delays A cycles + overhead
|
||||
; Preserved: BC, DE, HL
|
||||
; Time: A+20 cycles (including CALL)
|
||||
delay_a_20_cycles:
|
||||
- sub 5 ; 2
|
||||
jr nc,- ;3/2 do multiples of 5
|
||||
rra ; 1
|
||||
jr nc,+ ;3/2 bit 0
|
||||
+ adc 1 ; 2
|
||||
ret nc ;5/2 -1: 0 cycles
|
||||
ret z ;5/2 0: 2 cycles
|
||||
nop ; 1 1: 4 cycles
|
||||
ret ; 4 (thanks to dclxvi for original algorithm)
|
||||
|
||||
; Delays A*256 cycles + overhead
|
||||
; Preserved: BC, DE, HL
|
||||
; Time: A*256+12 cycles (including CALL)
|
||||
delay_256a_12_cycles:
|
||||
or a ; 1
|
||||
ret z ; 5/2
|
||||
delay_256a_9_cycles_:
|
||||
- delay 256-4
|
||||
dec a ; 1
|
||||
jr nz,- ;3/2
|
||||
ret ; 4
|
||||
|
||||
; Delays A*65536 cycles + overhead
|
||||
; Preserved: BC, DE, HL
|
||||
; Time: A*65536+12 cycles (including CALL)
|
||||
delay_65536a_12_cycles:
|
||||
or a ; 1
|
||||
ret z ;5/2
|
||||
delay_65536a_9_cycles_:
|
||||
- delay 65536-4
|
||||
dec a ; 1
|
||||
jr nz,- ;3/2
|
||||
ret ; 4
|
||||
|
||||
; Delays H*256+L cycles + overhead
|
||||
; Preserved: AF, BC, DE, HL
|
||||
; Time: H*256+L+51 cycles
|
||||
delay_hl_51_cycles:
|
||||
push af
|
||||
ld a,h
|
||||
call delay_256a_12_cycles
|
||||
ld a,l
|
||||
call delay_a_20_cycles
|
||||
pop af
|
||||
ret
|
||||
|
||||
; delay_short_ macro calls into these
|
||||
.ds max_short_delay-10,$00 ; NOP repeated several times
|
||||
delay_unrolled_:
|
||||
ret
|
||||
|
||||
.macro delay_short_ ARGS n
|
||||
.if n < 0
|
||||
.fail
|
||||
.endif
|
||||
.if n > max_short_delay
|
||||
.fail
|
||||
.endif
|
||||
|
||||
.if n == 1
|
||||
nop
|
||||
.endif
|
||||
.if n == 2
|
||||
nop
|
||||
nop
|
||||
.endif
|
||||
.if n == 3
|
||||
.byte $18,$00 ; JR +0
|
||||
.endif
|
||||
.if n == 4
|
||||
.byte $18,$00 ; JR +0
|
||||
nop
|
||||
.endif
|
||||
.if n == 5
|
||||
.byte $18,$00 ; JR +0
|
||||
nop
|
||||
nop
|
||||
.endif
|
||||
.if n == 6
|
||||
.byte $18,$00 ; JR +0
|
||||
.byte $18,$00 ; JR +0
|
||||
.endif
|
||||
.if n == 7
|
||||
push af
|
||||
pop af
|
||||
.endif
|
||||
.if n == 8
|
||||
push af
|
||||
pop af
|
||||
nop
|
||||
.endif
|
||||
.if n == 9
|
||||
push af
|
||||
pop af
|
||||
nop
|
||||
nop
|
||||
.endif
|
||||
.if n >= 10
|
||||
call delay_unrolled_ + 10 - n
|
||||
.endif
|
||||
.endm
|
||||
64
cpu_instrs/source/common/gb.inc
Normal file
64
cpu_instrs/source/common/gb.inc
Normal file
@@ -0,0 +1,64 @@
|
||||
; Game Boy hardware addresses
|
||||
|
||||
; Memory
|
||||
.define VRAM $8000 ; video memory
|
||||
.define TILES $8000 ; tile images
|
||||
.define BGMAP0 $9800 ; first 32x32 tilemap
|
||||
.define BGMAP1 $9C00 ; second 32x32 tilemap
|
||||
.define WRAM $C000 ; internal memory
|
||||
.define OAM $FE00 ; sprite memory
|
||||
.define HRAM $FF80 ; fast memory for LDH
|
||||
|
||||
.define P1 $FF00
|
||||
|
||||
; Game link I/O
|
||||
.define SB $FF01
|
||||
.define SC $FF02
|
||||
|
||||
; Interrupts
|
||||
.define DIV $FF04
|
||||
.define TIMA $FF05
|
||||
.define TMA $FF06
|
||||
.define TAC $FF07
|
||||
.define IF $FF0F
|
||||
.define IE $FFFF
|
||||
|
||||
; LCD registers
|
||||
.define LCDC $FF40 ; control
|
||||
.define STAT $FF41 ; status
|
||||
.define SCY $FF42 ; scroll Y
|
||||
.define SCX $FF43 ; scroll X
|
||||
.define LY $FF44 ; current Y being rendered
|
||||
.define BGP $FF47
|
||||
|
||||
.define KEY1 $FF4D ; for changing CPU speed
|
||||
.define VBK $FF4F
|
||||
|
||||
; Sound registers
|
||||
.define NR10 $FF10
|
||||
.define NR11 $FF11
|
||||
.define NR12 $FF12
|
||||
.define NR13 $FF13
|
||||
.define NR14 $FF14
|
||||
|
||||
.define NR21 $FF16
|
||||
.define NR22 $FF17
|
||||
.define NR23 $FF18
|
||||
.define NR24 $FF19
|
||||
|
||||
.define NR30 $FF1A
|
||||
.define NR31 $FF1B
|
||||
.define NR32 $FF1C
|
||||
.define NR33 $FF1D
|
||||
.define NR34 $FF1E
|
||||
|
||||
.define NR41 $FF20
|
||||
.define NR42 $FF21
|
||||
.define NR43 $FF22
|
||||
.define NR44 $FF23
|
||||
|
||||
.define NR50 $FF24
|
||||
.define NR51 $FF25
|
||||
.define NR52 $FF26
|
||||
|
||||
.define WAVE $FF30
|
||||
105
cpu_instrs/source/common/instr_test.s
Normal file
105
cpu_instrs/source/common/instr_test.s
Normal file
@@ -0,0 +1,105 @@
|
||||
; Framework for CPU instruction tests
|
||||
|
||||
; Calls test_instr with each instruction copied
|
||||
; to instr, with a JP instr_done after it.
|
||||
; Verifies checksum after testing instruction and
|
||||
; prints opcode if it's wrong.
|
||||
|
||||
.include "checksums.s"
|
||||
.include "cpu_speed.s"
|
||||
.include "apu.s"
|
||||
.include "crc_fast.s"
|
||||
|
||||
.define instr $DEF8
|
||||
.define rp_temp (instr-4)
|
||||
|
||||
.define temp bss
|
||||
|
||||
; Sets SP to word at addr
|
||||
; Preserved: BC, DE
|
||||
.macro ldsp ; addr
|
||||
ld a,(\1)
|
||||
ld l,a
|
||||
ld a,((\1)+1)
|
||||
ld h,a
|
||||
ld sp,hl
|
||||
.endm
|
||||
|
||||
main:
|
||||
call cpu_fast
|
||||
call init_crc_fast
|
||||
call checksums_init
|
||||
set_test 0
|
||||
|
||||
ld hl,instrs
|
||||
- ; Copy instruction
|
||||
ld a,(hl+)
|
||||
ld (instr),a
|
||||
ld a,(hl+)
|
||||
ld (instr+1),a
|
||||
ld a,(hl+)
|
||||
ld (instr+2),a
|
||||
push hl
|
||||
|
||||
; Put JP instr_done after it
|
||||
ld a,$C3
|
||||
ld (instr+3),a
|
||||
ld a,<instr_done
|
||||
ld (instr+4),a
|
||||
ld a,>instr_done
|
||||
ld (instr+5),a
|
||||
|
||||
call reset_crc
|
||||
call test_instr
|
||||
|
||||
call checksums_compare
|
||||
jr z,passed
|
||||
|
||||
set_test 1
|
||||
ld a,(instr)
|
||||
call print_a
|
||||
cp $CB
|
||||
jr nz,+
|
||||
ld a,(instr+1)
|
||||
call print_a
|
||||
+
|
||||
|
||||
passed:
|
||||
; Next instruction
|
||||
pop hl
|
||||
ld a,l
|
||||
cp <instrs_end
|
||||
jr nz,-
|
||||
ld a,h
|
||||
cp >instrs_end
|
||||
jr nz,-
|
||||
|
||||
jp tests_done
|
||||
|
||||
|
||||
; Updates checksum with AF, BC, DE, and HL
|
||||
checksum_af_bc_de_hl:
|
||||
push hl
|
||||
|
||||
push af
|
||||
update_crc_fast
|
||||
pop hl
|
||||
ld a,l
|
||||
update_crc_fast
|
||||
|
||||
ld a,b
|
||||
update_crc_fast
|
||||
ld a,c
|
||||
update_crc_fast
|
||||
|
||||
ld a,d
|
||||
update_crc_fast
|
||||
ld a,e
|
||||
update_crc_fast
|
||||
|
||||
pop de
|
||||
ld a,d
|
||||
update_crc_fast
|
||||
ld a,e
|
||||
update_crc_fast
|
||||
ret
|
||||
73
cpu_instrs/source/common/macros.inc
Normal file
73
cpu_instrs/source/common/macros.inc
Normal file
@@ -0,0 +1,73 @@
|
||||
; General macros
|
||||
|
||||
; Reads A from addr, from $FF00 to $FFFF
|
||||
; Preserved: F, BC, DE, HL
|
||||
; Time: 3 cycles
|
||||
.macro lda ARGS addr
|
||||
ldh a,(addr - $FF00)
|
||||
.endm
|
||||
|
||||
; Writes A to addr, from $FF00 to $FFFF
|
||||
; Preserved: AF, BC, DE, HL
|
||||
; Time: 3 cycles
|
||||
.macro sta ARGS addr
|
||||
ldh (addr - $FF00),a
|
||||
.endm
|
||||
|
||||
; Writes immediate data to addr, from $FF00 to $FFFF
|
||||
; Preserved: F, BC, DE, HL
|
||||
; Time: 5 cycles
|
||||
.macro wreg ARGS addr, data
|
||||
ld a,data
|
||||
sta addr
|
||||
.endm
|
||||
|
||||
; Calls routine multiple times, with A having the
|
||||
; value 'start' the first time, 'start+step' the
|
||||
; second time, up to 'end' for the last time.
|
||||
; Preserved: BC, DE, HL
|
||||
.macro for_loop ; routine,start,end,step
|
||||
ld a,\2
|
||||
|
||||
for_loop\@:
|
||||
push af
|
||||
call \1
|
||||
pop af
|
||||
|
||||
add \4
|
||||
cp <(\3 + \4)
|
||||
jr nz,for_loop\@
|
||||
.endm
|
||||
|
||||
; Calls routine n times. The value of A in the routine
|
||||
; counts from 0 to n-1.
|
||||
; Preserved: BC, DE, HL
|
||||
.macro loop_n_times ; routine,n
|
||||
for_loop \1,0,\2 - 1,+1
|
||||
.endm
|
||||
|
||||
; Same as for_loop, but counts with 16-bit value in BC.
|
||||
; Preserved: DE, HL
|
||||
.macro for_loop16 ; routine,start,end,step
|
||||
ld bc,\2
|
||||
|
||||
for_loop16\@:
|
||||
push bc
|
||||
call \1
|
||||
pop bc
|
||||
|
||||
ld a,c
|
||||
add <\4
|
||||
ld c,a
|
||||
|
||||
ld a,b
|
||||
adc >\4
|
||||
ld b,a
|
||||
|
||||
cp >(\3+\4)
|
||||
jr nz,for_loop16\@
|
||||
|
||||
ld a,c
|
||||
cp <(\3+\4)
|
||||
jr nz,for_loop16\@
|
||||
.endm
|
||||
38
cpu_instrs/source/common/multi_custom.s
Normal file
38
cpu_instrs/source/common/multi_custom.s
Normal file
@@ -0,0 +1,38 @@
|
||||
; RST handlers
|
||||
.bank 0 slot 0
|
||||
.org 0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
.ds 6,0
|
||||
inc a
|
||||
ret
|
||||
177
cpu_instrs/source/common/numbers.s
Normal file
177
cpu_instrs/source/common/numbers.s
Normal file
@@ -0,0 +1,177 @@
|
||||
; Printing of numeric values
|
||||
|
||||
; Prints value of indicated register/pair
|
||||
; as 2/4 hex digits, followed by a space.
|
||||
; Updates checksum with printed values.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
|
||||
print_regs:
|
||||
call print_af
|
||||
call print_bc
|
||||
call print_de
|
||||
call print_hl
|
||||
call print_newline
|
||||
ret
|
||||
|
||||
print_a:
|
||||
push af
|
||||
print_a_:
|
||||
call print_hex
|
||||
ld a,' '
|
||||
call print_char_nocrc
|
||||
pop af
|
||||
ret
|
||||
|
||||
print_af:
|
||||
push af
|
||||
call print_hex
|
||||
pop af
|
||||
print_f:
|
||||
push bc
|
||||
push af
|
||||
pop bc
|
||||
call print_c
|
||||
pop bc
|
||||
ret
|
||||
|
||||
print_b:
|
||||
push af
|
||||
ld a,b
|
||||
jr print_a_
|
||||
|
||||
print_c:
|
||||
push af
|
||||
ld a,c
|
||||
jr print_a_
|
||||
|
||||
print_d:
|
||||
push af
|
||||
ld a,d
|
||||
jr print_a_
|
||||
|
||||
print_e:
|
||||
push af
|
||||
ld a,e
|
||||
jr print_a_
|
||||
|
||||
print_h:
|
||||
push af
|
||||
ld a,h
|
||||
jr print_a_
|
||||
|
||||
print_l:
|
||||
push af
|
||||
ld a,l
|
||||
jr print_a_
|
||||
|
||||
print_bc:
|
||||
push af
|
||||
push bc
|
||||
print_bc_:
|
||||
ld a,b
|
||||
call print_hex
|
||||
ld a,c
|
||||
pop bc
|
||||
jr print_a_
|
||||
|
||||
print_de:
|
||||
push af
|
||||
push bc
|
||||
ld b,d
|
||||
ld c,e
|
||||
jr print_bc_
|
||||
|
||||
print_hl:
|
||||
push af
|
||||
push bc
|
||||
ld b,h
|
||||
ld c,l
|
||||
jr print_bc_
|
||||
|
||||
|
||||
; Prints A as two hex chars and updates checksum
|
||||
; Preserved: BC, DE, HL
|
||||
print_hex:
|
||||
call update_crc
|
||||
print_hex_nocrc:
|
||||
push af
|
||||
swap a
|
||||
call +
|
||||
pop af
|
||||
|
||||
+ and $0F
|
||||
cp 10
|
||||
jr c,+
|
||||
add 7
|
||||
+ add '0'
|
||||
jp print_char_nocrc
|
||||
|
||||
|
||||
; Prints char_nz if Z flag is clear,
|
||||
; char_z if Z flag is set.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
.macro print_nz ARGS char_nz, char_z
|
||||
push af
|
||||
ld a,char_nz
|
||||
jr nz,print_nz\@
|
||||
ld a,char_z
|
||||
print_nz\@:
|
||||
call print_char
|
||||
pop af
|
||||
.endm
|
||||
|
||||
|
||||
; Prints char_nc if C flag is clear,
|
||||
; char_c if C flag is set.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
.macro print_nc ARGS char_nc, char_c
|
||||
push af
|
||||
ld a,char_nc
|
||||
jr nz,print_nc\@
|
||||
ld a,char_c
|
||||
print_nc\@:
|
||||
call print_char
|
||||
pop af
|
||||
.endm
|
||||
|
||||
|
||||
; Prints A as 2 decimal digits
|
||||
; Preserved: AF, BC, DE, HL
|
||||
print_dec2:
|
||||
push af
|
||||
push bc
|
||||
jr +
|
||||
|
||||
|
||||
; Prints A as 1-3 digit decimal value
|
||||
; Preserved: AF, BC, DE, HL
|
||||
print_dec:
|
||||
push af
|
||||
push bc
|
||||
|
||||
cp 10
|
||||
jr c,++
|
||||
ld c,100
|
||||
cp c
|
||||
call nc,@digit
|
||||
+ ld c,10
|
||||
call @digit
|
||||
++ add '0'
|
||||
call print_char
|
||||
|
||||
pop bc
|
||||
pop af
|
||||
ret
|
||||
|
||||
@digit:
|
||||
ld b,'0'-1
|
||||
- inc b
|
||||
sub c
|
||||
jr nc,-
|
||||
add c
|
||||
|
||||
ld c,a
|
||||
ld a,b
|
||||
call print_char
|
||||
ld a,c
|
||||
ret
|
||||
98
cpu_instrs/source/common/printing.s
Normal file
98
cpu_instrs/source/common/printing.s
Normal file
@@ -0,0 +1,98 @@
|
||||
; Main printing routine that checksums and
|
||||
; prints to output device
|
||||
|
||||
; Character that does equivalent of print_newline
|
||||
.define newline 10
|
||||
|
||||
; Prints char without updating checksum
|
||||
; Preserved: BC, DE, HL
|
||||
.define print_char_nocrc bss
|
||||
.redefine bss bss+3
|
||||
|
||||
|
||||
; Initializes printing. HL = print routine
|
||||
init_printing:
|
||||
ld a,l
|
||||
ld (print_char_nocrc+1),a
|
||||
ld a,h
|
||||
ld (print_char_nocrc+2),a
|
||||
jr show_printing
|
||||
|
||||
|
||||
; Hides/shows further printing
|
||||
; Preserved: BC, DE, HL
|
||||
hide_printing:
|
||||
ld a,$C9 ; RET
|
||||
jr +
|
||||
show_printing:
|
||||
ld a,$C3 ; JP (nn)
|
||||
+ ld (print_char_nocrc),a
|
||||
ret
|
||||
|
||||
|
||||
; Prints character and updates checksum UNLESS
|
||||
; it's a newline.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
print_char:
|
||||
push af
|
||||
cp newline
|
||||
call nz,update_crc
|
||||
call print_char_nocrc
|
||||
pop af
|
||||
ret
|
||||
|
||||
|
||||
; Prints space. Does NOT update checksum.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
print_space:
|
||||
push af
|
||||
ld a,' '
|
||||
call print_char_nocrc
|
||||
pop af
|
||||
ret
|
||||
|
||||
|
||||
; Advances to next line. Does NOT update checksum.
|
||||
; Preserved: AF, BC, DE, HL
|
||||
print_newline:
|
||||
push af
|
||||
ld a,newline
|
||||
call print_char_nocrc
|
||||
pop af
|
||||
ret
|
||||
|
||||
|
||||
; Prints immediate string
|
||||
; Preserved: AF, BC, DE, HL
|
||||
.macro print_str ; string,string2
|
||||
push hl
|
||||
call print_str_
|
||||
.byte \1
|
||||
.if NARGS > 1
|
||||
.byte \2
|
||||
.endif
|
||||
.if NARGS > 2
|
||||
.byte \3
|
||||
.endif
|
||||
.byte 0
|
||||
pop hl
|
||||
.endm
|
||||
|
||||
print_str_:
|
||||
pop hl
|
||||
call print_str_hl
|
||||
jp hl
|
||||
|
||||
|
||||
; Prints zero-terminated string pointed to by HL.
|
||||
; On return, HL points to byte AFTER zero terminator.
|
||||
; Preserved: AF, BC, DE
|
||||
print_str_hl:
|
||||
push af
|
||||
jr +
|
||||
- call print_char
|
||||
+ ldi a,(hl)
|
||||
or a
|
||||
jr nz,-
|
||||
pop af
|
||||
ret
|
||||
142
cpu_instrs/source/common/runtime.s
Normal file
142
cpu_instrs/source/common/runtime.s
Normal file
@@ -0,0 +1,142 @@
|
||||
; Common routines and runtime
|
||||
|
||||
; Must be defined by target-specific runtime:
|
||||
;
|
||||
; init_runtime: ; target-specific inits
|
||||
; std_print: ; default routine to print char A
|
||||
; post_exit: ; called at end of std_exit
|
||||
; report_byte: ; report A to user
|
||||
|
||||
.define RUNTIME_INCLUDED 1
|
||||
|
||||
.ifndef bss
|
||||
; address of next normal variable
|
||||
.define bss $D800
|
||||
.endif
|
||||
|
||||
.ifndef dp
|
||||
; address of next direct-page ($FFxx) variable
|
||||
.define dp $FF80
|
||||
.endif
|
||||
|
||||
; DMG/CGB hardware identifier
|
||||
.define gb_id_cgb $10 ; mask for testing CGB bit
|
||||
.define gb_id_devcart $04 ; mask for testing "on devcart" bit
|
||||
|
||||
.define gb_id bss
|
||||
.redefine bss bss+1
|
||||
|
||||
; Stack is normally here
|
||||
.define std_stack $DFFF
|
||||
|
||||
; Copies $1000 bytes from HL to $C000, then jumps to it.
|
||||
; A is preserved for jumped-to code.
|
||||
copy_to_wram_then_run:
|
||||
ld b,a
|
||||
|
||||
ld de,$C000
|
||||
ld c,$10
|
||||
- ldi a,(hl)
|
||||
ld (de),a
|
||||
inc e
|
||||
jr nz,-
|
||||
inc d
|
||||
dec c
|
||||
jr nz,-
|
||||
|
||||
ld a,b
|
||||
jp $C000
|
||||
|
||||
.ifndef CUSTOM_RESET
|
||||
reset:
|
||||
; Run code from $C000, as is done on devcart. This
|
||||
; ensures minimal difference in how it behaves.
|
||||
ld hl,$4000
|
||||
jp copy_to_wram_then_run
|
||||
|
||||
.bank 1 slot 1
|
||||
.org $0 ; otherwise wla pads with lots of zeroes
|
||||
jp std_reset
|
||||
.endif
|
||||
|
||||
; Common routines
|
||||
.include "gb.inc"
|
||||
.include "macros.inc"
|
||||
.include "delay.s"
|
||||
.include "crc.s"
|
||||
.include "printing.s"
|
||||
.include "numbers.s"
|
||||
.include "testing.s"
|
||||
|
||||
; Sets up hardware and runs main
|
||||
std_reset:
|
||||
|
||||
; Init hardware
|
||||
di
|
||||
ld sp,std_stack
|
||||
|
||||
; Save DMG/CGB id
|
||||
ld (gb_id),a
|
||||
|
||||
; Init hardware
|
||||
.ifndef BUILD_GBS
|
||||
wreg TAC,$00
|
||||
wreg IF,$00
|
||||
wreg IE,$00
|
||||
.endif
|
||||
|
||||
wreg NR52,0 ; sound off
|
||||
wreg NR52,$80 ; sound on
|
||||
wreg NR51,$FF ; mono
|
||||
wreg NR50,$77 ; volume
|
||||
|
||||
; TODO: clear all memory?
|
||||
|
||||
ld hl,std_print
|
||||
call init_printing
|
||||
call init_testing
|
||||
call init_runtime
|
||||
call reset_crc ; in case init_runtime prints anything
|
||||
|
||||
delay_msec 250
|
||||
|
||||
; Run user code
|
||||
call main
|
||||
|
||||
; Default is to successful exit
|
||||
ld a,0
|
||||
jp exit
|
||||
|
||||
|
||||
; Exits code and reports value of A
|
||||
exit:
|
||||
ld sp,std_stack
|
||||
push af
|
||||
call +
|
||||
pop af
|
||||
jp post_exit
|
||||
|
||||
+ push af
|
||||
call print_newline
|
||||
call show_printing
|
||||
pop af
|
||||
|
||||
; Report exit status
|
||||
cp 1
|
||||
|
||||
; 0: ""
|
||||
ret c
|
||||
|
||||
; 1: "Failed"
|
||||
jr nz,+
|
||||
print_str "Failed",newline
|
||||
ret
|
||||
|
||||
; n: "Failed #n"
|
||||
+ print_str "Failed #"
|
||||
call print_dec
|
||||
call print_newline
|
||||
ret
|
||||
|
||||
; returnOrg puts this code AFTER user code.
|
||||
.section "runtime" returnOrg
|
||||
176
cpu_instrs/source/common/testing.s
Normal file
176
cpu_instrs/source/common/testing.s
Normal file
@@ -0,0 +1,176 @@
|
||||
; Diagnostic and testing utilities
|
||||
|
||||
.define result bss+0
|
||||
.define test_name bss+1
|
||||
.redefine bss bss+3
|
||||
|
||||
|
||||
; Sets test code and optional error text
|
||||
; Preserved: AF, BC, DE, HL
|
||||
.macro set_test ; code[,text[,text2]]
|
||||
push hl
|
||||
call set_test_
|
||||
jr @set_test\@
|
||||
.byte \1
|
||||
.if NARGS > 1
|
||||
.byte \2
|
||||
.endif
|
||||
.if NARGS > 2
|
||||
.byte \3
|
||||
.endif
|
||||
.byte 0
|
||||
@set_test\@:
|
||||
pop hl
|
||||
.endm
|
||||
|
||||
set_test_:
|
||||
pop hl
|
||||
push hl
|
||||
push af
|
||||
inc hl
|
||||
inc hl
|
||||
ldi a,(hl)
|
||||
ld (result),a
|
||||
ld a,l
|
||||
ld (test_name),a
|
||||
ld a,h
|
||||
ld (test_name+1),a
|
||||
pop af
|
||||
ret
|
||||
|
||||
|
||||
; Initializes testing module
|
||||
init_testing:
|
||||
set_test $FF
|
||||
call init_crc
|
||||
ret
|
||||
|
||||
|
||||
; Reports "Passed", then exits with code 0
|
||||
tests_passed:
|
||||
call print_newline
|
||||
print_str "Passed"
|
||||
ld a,0
|
||||
jp exit
|
||||
|
||||
|
||||
; Reports "Done" if set_test has never been used,
|
||||
; "Passed" if set_test 0 was last used, or
|
||||
; failure if set_test n was last used.
|
||||
tests_done:
|
||||
ld a,(result)
|
||||
inc a
|
||||
jr z,+
|
||||
dec a
|
||||
jr z,tests_passed
|
||||
jr test_failed
|
||||
+ print_str "Done"
|
||||
ld a,0
|
||||
jp exit
|
||||
|
||||
|
||||
; Reports current error text and exits with result code
|
||||
test_failed:
|
||||
ld a,(test_name)
|
||||
ld l,a
|
||||
ld a,(test_name+1)
|
||||
ld h,a
|
||||
ld a,(hl)
|
||||
or a
|
||||
jr z,+
|
||||
call print_newline
|
||||
call print_str_hl
|
||||
call print_newline
|
||||
+
|
||||
ld a,(result)
|
||||
cp 1 ; if a = 0 then a = 1
|
||||
adc 0
|
||||
jp exit
|
||||
|
||||
|
||||
; Prints checksum as 8-character hex value
|
||||
; Preserved: AF, BC, DE, HL
|
||||
print_crc:
|
||||
push af
|
||||
|
||||
; Must read checksum entirely before printing,
|
||||
; since printing updates it.
|
||||
lda checksum
|
||||
cpl
|
||||
push af
|
||||
|
||||
lda checksum+1
|
||||
cpl
|
||||
push af
|
||||
|
||||
lda checksum+2
|
||||
cpl
|
||||
push af
|
||||
|
||||
lda checksum+3
|
||||
cpl
|
||||
|
||||
call print_hex
|
||||
pop af
|
||||
call print_hex
|
||||
pop af
|
||||
call print_hex
|
||||
pop af
|
||||
call print_a
|
||||
|
||||
pop af
|
||||
ret
|
||||
|
||||
|
||||
; If checksum doesn't match expected, reports failed test.
|
||||
; Passing 0 just prints checksum. Clears checksum afterwards.
|
||||
.macro check_crc ARGS crc
|
||||
.if crc == 0
|
||||
call show_printing
|
||||
call print_newline
|
||||
call print_crc
|
||||
.else
|
||||
ld bc,(crc >> 16) ~ $FFFF
|
||||
ld de,(crc & $FFFF) ~ $FFFF
|
||||
call check_crc_
|
||||
.endif
|
||||
.endm
|
||||
|
||||
check_crc_:
|
||||
lda checksum+0
|
||||
cp e
|
||||
jr nz,+
|
||||
|
||||
lda checksum+1
|
||||
cp d
|
||||
jr nz,+
|
||||
|
||||
lda checksum+2
|
||||
cp c
|
||||
jr nz,+
|
||||
|
||||
lda checksum+3
|
||||
cp b
|
||||
jr nz,+
|
||||
|
||||
jp reset_crc
|
||||
|
||||
+ call print_crc
|
||||
jp test_failed
|
||||
|
||||
|
||||
; Updates checksum with bytes from addr to addr+size-1
|
||||
.macro checksum_mem ARGS addr,size
|
||||
ld hl,addr
|
||||
ld bc,size
|
||||
call checksum_mem_
|
||||
.endm
|
||||
|
||||
checksum_mem_:
|
||||
- ldi a,(hl)
|
||||
call update_crc
|
||||
dec bc
|
||||
ld a,b
|
||||
or c
|
||||
jr nz,-
|
||||
ret
|
||||
2
cpu_instrs/source/linkfile
Normal file
2
cpu_instrs/source/linkfile
Normal file
@@ -0,0 +1,2 @@
|
||||
[objects]
|
||||
test.o
|
||||
21
cpu_instrs/source/shell.inc
Normal file
21
cpu_instrs/source/shell.inc
Normal file
@@ -0,0 +1,21 @@
|
||||
.incdir "common"
|
||||
|
||||
; GBS music file
|
||||
.ifdef BUILD_GBS
|
||||
.include "build_gbs.s"
|
||||
.endif
|
||||
|
||||
; Devcart
|
||||
.ifdef BUILD_DEVCART
|
||||
.include "build_devcart.s"
|
||||
.endif
|
||||
|
||||
; Sub-test in a multi-test ROM
|
||||
.ifdef BUILD_MULTI
|
||||
.include "build_multi.s"
|
||||
.endif
|
||||
|
||||
; GB ROM (default)
|
||||
.ifndef RUNTIME_INCLUDED
|
||||
.include "build_rom.s"
|
||||
.endif
|
||||
Reference in New Issue
Block a user