]> Joshua Wise's Git repositories - fpgaboy.git/blobdiff - diag.asm
Add DI/EI delay test. Add LD M, A.
[fpgaboy.git] / diag.asm
index 68ea3f8e9e42ebe67e66a67e594202f182a61070..55127f82cff8704fd3c716ebdd22f43b2ff1e28e 100644 (file)
--- a/diag.asm
+++ b/diag.asm
@@ -7,20 +7,62 @@ main:
        
        ld sp, $DFF0
        
        
        ld sp, $DFF0
        
+       ld c, $07
+       ld a, $04       ;start timer, 4.096KHz
+       ld [c], a
+
+       ld hl, $DF81
+       xor a
+       ld [hli], a
+       ld [hli], a
+       
        ld hl, signon
        call puts
        ld hl, signon
        call puts
+       
+       ei
 
        call memtest
 
        call insntest
 
        call waitsw
 
        call memtest
 
        call insntest
 
        call waitsw
+       
+       di
 
        jr main
 
 signon:
        db $0D,$0A,$1B,"[1mFPGABoy Diagnostic ROM",$1B,"[0m",$0D,$0A,0
 
 
        jr main
 
 signon:
        db $0D,$0A,$1B,"[1mFPGABoy Diagnostic ROM",$1B,"[0m",$0D,$0A,0
 
+       section "fuq",HOME[$100]
+irqhand:
+       PUSH AF
+       PUSH BC
+       PUSH DE
+       PUSH HL
+       
+       xor a
+       ld c, $0F       ; ack the irq
+       ld [c], a
+       
+       ld hl, $DF82
+       ld a, [hld]
+       cp 0
+       jr z, .noprint
+       ld a, $41       ; print A
+       call putc
+.noprint:
+       inc [hl]
+       ld a, [hl]
+       ld c, $51
+       ld [c], a
+
+       POP HL
+       POP DE
+       POP BC
+       POP AF
+       RETI
+
 ; Memory tester: writes h ^ l to all addresses from C000 to DF80.
 memtest:
        ld hl,memteststr
 ; Memory tester: writes h ^ l to all addresses from C000 to DF80.
 memtest:
        ld hl,memteststr
@@ -31,11 +73,11 @@ memtest:
        ld a,h
        xor l
        ld [hli],a
        ld a,h
        xor l
        ld [hli],a
-       ld a, $DF
-       cp h
+       ld a, h
+       cp $DF
        jr nz, .wr
        jr nz, .wr
-       ld a, $80
-       cp l
+       ld a, l
+       cp $80
        jr nz, .wr
 
        ld hl, $C001            ; Read loop
        jr nz, .wr
 
        ld hl, $C001            ; Read loop
@@ -47,11 +89,11 @@ memtest:
        cp b
        jr nz, .memfail
        
        cp b
        jr nz, .memfail
        
-       ld a, $DF
-       cp h
+       ld a, h
+       cp $DF
        jr nz, .rd
        jr nz, .rd
-       ld a, $80
-       cp l
+       ld a, l
+       cp $80
        jr nz, .rd
        
        ld hl, testokstr        ; Say we're OK
        jr nz, .rd
        
        ld hl, testokstr        ; Say we're OK
@@ -86,16 +128,12 @@ puthex:                            ; Put two hex nibbles to the serial console.
        rra
        rra
        rra
        rra
        rra
        rra
-       ld b,$0F
-       and b
-       ld b,$30
-       add b
+       and $0F
+       add $30
        call putc
        pop af
        call putc
        pop af
-       ld b,$0F
-       and b
-       ld b,$30
-       add b
+       and $0F
+       add $30
        call putc
        ret
 
        call putc
        ret
 
@@ -103,19 +141,22 @@ puthex:                           ; Put two hex nibbles to the serial console.
 waitsw:
        ld hl,waitswstr
        call puts
 waitsw:
        ld hl,waitswstr
        call puts
+       
+       ld hl,$DF82
+       ld a, 1
+       ld [hl], a
 
        ld c, $51
        xor a
        ld [c],a
        
 
        ld c, $51
        xor a
        ld [c],a
        
-       ld b, $0
 .loop1:
        ld a,[c]
 .loop1:
        ld a,[c]
-       cp b
+       cp $0
        jr z,.loop1
 .loop2:
        ld a,[c]
        jr z,.loop1
 .loop2:
        ld a,[c]
-       cp b
+       cp $0
        jr nz,.loop2
        ret
 
        jr nz,.loop2
        ret
 
@@ -159,8 +200,7 @@ insntest:
 
        ; Test JR
        ld a, $FF
 
        ; Test JR
        ld a, $FF
-       ld b, $00
-       cp b
+       cp $0
        jr nz,.jr
        ld hl, .jrfail
        jr .fail
        jr nz,.jr
        ld hl, .jrfail
        jr .fail
@@ -182,26 +222,44 @@ insntest:
        ; Test CP.
        ld hl, .cpfail
        ld a, $10
        ; Test CP.
        ld hl, .cpfail
        ld a, $10
-       ld b, $20
-       cp b
+       cp $20
        jr nc,.fail
        ld a, $20
        jr nc,.fail
        ld a, $20
-       ld b, $10
-       cp b
+       cp $10
        jr c,.fail
        
        ; Test CPL
        ld hl, .cplfail
        ld a, $55
        jr c,.fail
        
        ; Test CPL
        ld hl, .cplfail
        ld a, $55
-       ld b, $AA
        cpl
        cpl
-       cp b
+       cp $AA
        jr nz,.fail
        jr nz,.fail
+
+       ; Test DI/EI delay
+       di
+       ld hl, .difail
+       ld c, $0F       ; First, wait until an interrupt happens...
+.wait: ld a, [c]
+       cp 0
+       jr z, .wait
+       ei              ; Now make sure that an IRQ didn't happen on EI/DI
+       di
+       ld a, [c]
+       cp 0
+       jr z, .fail
+       ei              ; Make sure that an IRQ does happen on EI/NOP/DI
+       nop
+       di
+       ld a, [c]
+       cp 0
+       jr nz, .fail
+       ei
        
        ld hl, .ok
        call puts
        ret
 .fail:
        
        ld hl, .ok
        call puts
        ret
 .fail:
+       ei
        call puts
        ld hl, .testfailed
        call puts
        call puts
        ld hl, .testfailed
        call puts
@@ -224,6 +282,8 @@ insntest:
        db "CPL",0
 .inc16fail:
        db "INC16",0
        db "CPL",0
 .inc16fail:
        db "INC16",0
+.difail:
+       db "DI/EI delay",0
 .testfailed:
        db " test failed.",$0D,$0A,0
 .ok:
 .testfailed:
        db " test failed.",$0D,$0A,0
 .ok:
@@ -231,12 +291,11 @@ insntest:
 
 ; Serial port manipulation functions.
 putc:
 
 ; Serial port manipulation functions.
 putc:
-       ld b, 0
        ld c, $50
        push af
 .waitport:
        ld a,[c]
        ld c, $50
        push af
 .waitport:
        ld a,[c]
-       cp b
+       cp $00
        jr nz,.waitport
        pop af
        ld [c],a
        jr nz,.waitport
        pop af
        ld [c],a
@@ -244,8 +303,7 @@ putc:
 
 puts:
        ld a, [hli]
 
 puts:
        ld a, [hli]
-       ld b, $00
-       cp b
+       cp $00
        ret z
        call putc
        jr puts
        ret z
        call putc
        jr puts
This page took 0.027644 seconds and 4 git commands to generate.