Register & stack dump (ML)

Basic and Machine Language

Moderator: Moderators

Post Reply
Kananga
Vic 20 Afficionado
Posts: 317
Joined: Mon Mar 08, 2010 2:11 pm

Register & stack dump (ML)

Post by Kananga »

When my program detects something wrong, it calls a "panic" routine that displays an empty "blue screen".

Code: Select all

panic:		sei
			lda #0		; columns
			sta $9002
			lda #$6E	; all blue
			sta $900F
@ploop:		jmp @ploop
I used it mainly to set a breakpoint on "panic" and if the breakpoint is hit, I have enough information to analyse the problem.
On the real Vic that doesn't work and some information about the cause would be great.

Has anybody an ML snippet I could "borrow" at hand that dumps register values and stack contents to screen?
Buy the new Bug-Wizard, the first 100 bugs are free!
Kananga
Vic 20 Afficionado
Posts: 317
Joined: Mon Mar 08, 2010 2:11 pm

Post by Kananga »

Problem solved.
If anybody else needs it, it's part of the vin20 source.
Buy the new Bug-Wizard, the first 100 bugs are free!
FD22
Vic 20 Hobbyist
Posts: 148
Joined: Mon Feb 15, 2010 12:31 pm

Post by FD22 »

I had a think about this, and came up with some code that does a BSOD-like display when the CPU hits a BRK instruction - the idea is that you set the BRK vector at $0316/17 to point to the BSOD routine, which makes debugging fairly easy as you can just drop a BRK into your code where-ever you want to 'panic'. :wink:

Here's BSOD, which weighs-in at a chunky 479 bytes, but is giving you a 'pretty' display:
Image

Code: Select all

;-------------------------------------------------------------------------------
; BSOD
; Displays a Blue Screen of Death with register information when BRK encountered.
; Note: set BRK vector at $0316-0317 to point to this routine

bsod			SUBROUTINE
					sei										; Disable interrupts

					pla										; Pull .Y from stack
         	sta P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6y
         	lda P0FREE+2
         	sta .bsodm6y+1

					pla										; Pull .X from stack
         	sta P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6x
         	lda P0FREE+2
         	sta .bsodm6x+1

					pla										; Pull .A from stack
         	sta P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6a
         	lda P0FREE+2
         	sta .bsodm6a+1

         	pla										; Pull .SR from stack (BRK)
         	sta P0FREE						; Save to zero-page

         	; Cycle the .SR bits out for the flags line
         	lda #"1"							; Bit-set indicator
         	ldx #14								; Flag character index in .X
.cycle   	ror	P0FREE						; Sets/clears Carry to bit value
         	bcc .nextbit					; Carry clear, so skip to next bit
         	sta .bsodm8n,x				; Set bit indicator
.nextbit 	dex										; Decrement flag character index
         	dex
         	bpl .cycle						; Loop for next bit if not all done
					ror	P0FREE						; Final rotate to return to start value

         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6sr
         	lda P0FREE+2
         	sta .bsodm6sr+1

         	pla										; Pull .PCL from stack (BRK)
         	sec										; Set Carry
         	sbc #2								; Compensate PCL for BRK
					sta P0FREE						; Save to zero-page
         	bvc .pchok						; Overflow is clear when result >=0

         	; If PCL underflowed when we subtracted 2, adjust PCH down as well
         	pla										; Pull .PCH from stack (BRK)
         	sec										; Set Carry
         	sbc #1								; Subtraction because PCL underflowed
         	pha										; Push it back to stack

.pchok   	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6pc+2
         	lda P0FREE+2
         	sta .bsodm6pc+3

         	pla										; Pull .PCH from stack (BRK)
         	sta P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6pc
         	lda P0FREE+2
         	sta .bsodm6pc+1

         	tsx										; Move .SP to .X
         	stx P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6sp
         	lda P0FREE+2
         	sta .bsodm6sp+1

         	jsr CINT1							; Reset VIC
         	lda #110   						; Blue screen
         	sta SCRNCOL
         	lda #1								; White text
         	sta	CURRCOL
         	jsr CLRSCRN						; Clear the screen

         	dcprint bsodm1				; Error title
         	dcprint bsodm5				; Hyphens
         	jsr GONXTLN						; Skip a line
         	dcprint bsodm2				; Data title
         	dcprint bsodm5				; Hyphens
         	dcprint bsodm3				; Register headings
         	dcprint bsodm6				; Register contents

         	jsr GONXTLN						; Skip a line
         	jsr GONXTLN						; Skip a line
         	dcprint bsodm7				; Flags title
         	dcprint bsodm8				; Flag bits
         	dcprint bsodm5				; Hyphens
         	dcprint bsodm4				; End of Line gag

         	jsr GONXTLN						; Skip a line
         	dcprint bsodm5				; Hyphens

         	;DC.B $02							; HLT - stop CPU (UNDOCUMENTED OPCODE - not in DASM lexicon)
         	jmp *									; Endless loop - use if you don't want HLT

					; Information message strings
bsodm1		DC.B " * APPLICATION BREAK *"
					DC.B 0
bsodm2		DC.B " TECHNICAL INFORMATION"
					DC.B 0
bsodm3		DC.B "   PC  AC XR YR SP SR"
					DC.B 13,13,10,0
bsodm4		DC.B "  *** END OF LINE ***"
					DC.B 13,10,0
bsodm5		DC.B " ---------------------"
					DC.B 13,10,0
bsodm6		DC.B "  "
.bsodm6pc	DS.B 4,"0000"
					DC.B " "
.bsodm6a	DS.B 2,"00"
					DC.B " "
.bsodm6x	DS.B 2,"00"
					DC.B " "
.bsodm6y	DS.B 2,"00"
					DC.B " "
.bsodm6sp	DS.B 2,"00"
					DC.B " "
.bsodm6sr	DS.B 2,"00"
					DC.B 13,10,0
bsodm7		DC.B "  SR : N V - B D I Z C"
					DC.B 13,10,0
bsodm8		DC.B "       "
.bsodm8n	DS.B 1,"0"
					DC.B " "
.bsodm8v	DS.B 1,"0"
					DC.B " "
.bsodm8u	DS.B 1,"0"
					DC.B " "
.bsodm8b	DS.B 1,"0"
					DC.B " "
.bsodm8d	DS.B 1,"0"
					DC.B " "
.bsodm8i	DS.B 1,"0"
					DC.B " "
.bsodm8z	DS.B 1,"0"
					DC.B " "
.bsodm8c	DS.B 1,"0"
					DC.B 13,10,0
And here's BSODLITE, which does much the same but with less prettiness, and at only 300 bytes:
Image

Code: Select all

;-------------------------------------------------------------------------------
; BSODLITE
; Displays a mini-Blue Screen of Death with register information when BRK encountered.
; Note: set BRK vector at $0316-0317 to point to this routine

bsodlite	SUBROUTINE
					sei										; Disable interrupts

					pla										; Pull .Y from stack
         	sta P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6y
         	lda P0FREE+2
         	sta .bsodm6y+1

					pla										; Pull .X from stack
         	sta P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6x
         	lda P0FREE+2
         	sta .bsodm6x+1

					pla										; Pull .A from stack
         	sta P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6a
         	lda P0FREE+2
         	sta .bsodm6a+1

         	pla										; Pull .SR from stack (BRK)
         	sta P0FREE						; Save to zero-page

         	; Cycle the .SR bits out for the flags line
         	lda #"1"							; Bit-set indicator
         	ldx #7								; Flag character index in .X
.cycle   	ror	P0FREE						; Sets/clears Carry to bit value
         	bcc .nextbit					; Carry clear, so skip to next bit
         	sta .bsodm8n,x				; Set bit indicator
.nextbit 	dex										; Decrement flag character index
         	bpl .cycle						; Loop for next bit if not all done
					ror	P0FREE						; Final rotate to return to start value

         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6sr
         	lda P0FREE+2
         	sta .bsodm6sr+1

         	pla										; Pull .PCL from stack (BRK)
         	sec										; Set Carry
         	sbc #2								; Compensate PCL for BRK
					sta P0FREE						; Save to zero-page
         	bvc .pchok						; Overflow is clear when result >=0

         	; If PCL underflowed when we subtracted 2, adjust PCH down as well
         	pla										; Pull .PCH from stack (BRK)
         	sec										; Set Carry
         	sbc #1								; Subtraction because PCL underflowed
         	pha										; Push it back to stack

.pchok   	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6pc+2
         	lda P0FREE+2
         	sta .bsodm6pc+3

         	pla										; Pull .PCH from stack (BRK)
         	sta P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6pc
         	lda P0FREE+2
         	sta .bsodm6pc+1

         	tsx										; Move .SP to .X
         	stx P0FREE						; Save to zero-page
         	jsr dec2hex						; Convert to hex
         	lda P0FREE+1					; Copy to contents line
         	sta .bsodm6sp
         	lda P0FREE+2
         	sta .bsodm6sp+1

         	jsr CINT1							; Reset VIC
         	lda #110   						; Blue screen
         	sta SCRNCOL
         	lda #1								; White text
         	sta	CURRCOL
         	jsr CLRSCRN						; Clear the screen

         	dcprint bsodm3				; Register headings
         	dcprint bsodm6				; Register contents

         	jsr GONXTLN						; Skip a line
         	dcprint bsodm7				; Flags title
         	dcprint bsodm8				; Flag bits

         	;DC.B $02							; HLT - stop CPU (UNDOCUMENTED OPCODE - not in DASM lexicon)
         	jmp *									; Endless loop - use if you don't want HLT

					; Information message strings
bsodm3		DC.B " PC  AC XR YR SP SR"
					DC.B 13,10,0
bsodm6
.bsodm6pc	DS.B 4,"0000"
					DC.B " "
.bsodm6a	DS.B 2,"00"
					DC.B " "
.bsodm6x	DS.B 2,"00"
					DC.B " "
.bsodm6y	DS.B 2,"00"
					DC.B " "
.bsodm6sp	DS.B 2,"00"
					DC.B " "
.bsodm6sr	DS.B 2,"00"
					DC.B 13,10,0
bsodm7		DC.B " SR: NV-BDIZC"
					DC.B 13,10,0
bsodm8		DC.B "     "
.bsodm8n	DS.B 1,"0"
.bsodm8v	DS.B 1,"0"
.bsodm8u	DS.B 1,"0"
.bsodm8b	DS.B 1,"0"
.bsodm8d	DS.B 1,"0"
.bsodm8i	DS.B 1,"0"
.bsodm8z	DS.B 1,"0"
.bsodm8c	DS.B 1,"0"
					DC.B 0
You'll need to have the DEC2HEX subroutine and the DCPRINT macro available as well:

Code: Select all

;-------------------------------------------------------------------------------
; DEC2HEX
; Convert 8-bit binary in $fb to two hex characters in $fc and $fd

dec2hex		SUBROUTINE
          lax P0FREE            ; Get the original byte into .A and .X (UNDOCUMENTED OPCODE)
          and #$0f 	            ; Mask-off upper nybble
          tay                   ; Stash index in .Y
          lda .chars,y					; Get character
          sta P0FREE+2          ; Save it in the hex string
          txa                   ; Get the original byte again
          lsr                   ; Shift right one bit
          lsr                   ; Shift right one bit
          lsr                   ; Shift right one bit
          lsr                   ; Shift right one bit
          tay                   ; Stash index in .Y
          lda .chars,y  	      ; Get character
          sta P0FREE+1     	    ; Save it in the hex string
          rts

          ; Conversion table
.chars    DC.B "0123456789ABCDEF"

Code: Select all

;-------------------------------------------------------------------------------
; DCPRINT address
; Created by Valarian

; Call the VIC-20 ROM 'PRINT' routine.
; Parameters are:
;		address		- start address of zero-terminated string to print

					MAC DCPRINT
					lda #<{1}												; .A contains MSB of message start address
					ldy #>{1}												; .Y contains LSB of message start address
					jsr STROUT											; Call ROM routine
					ENDM
Making it work is just a matter of:

Code: Select all

					lda #<bsod
					sta BRKVEC
					lda #>bsod
					sta BRKVEC+1

					brk
Oh, you'll need my VICMAP file as well for the memory-map label definitions: http://vicdev.googlecode.com/files/VICMap.6502
Kananga
Vic 20 Afficionado
Posts: 317
Joined: Mon Mar 08, 2010 2:11 pm

Post by Kananga »

Thanks, nice blue screen, indeed! :)
Yes, a BRK handler is the only way to get register contents.

Did you take a look at my solution (http://code.google.com/p/vin20/source/b ... /panic.asm)?
It does not print registers, but dumps stack contents, which is quite important to locate the source of the fault.

Image
Buy the new Bug-Wizard, the first 100 bugs are free!
FD22
Vic 20 Hobbyist
Posts: 148
Joined: Mon Feb 15, 2010 12:31 pm

Post by FD22 »

Just looked at your code - it seems similar to mine, but that's hardly surprising since they do much the same. ;)

I'm working on an optimised version which is smaller than my first attempt by about 30%, fully relocatable (no JMPs) and dumps the first few bytes of the stack as well. It'll be more 'functional' in appearance, since I ended-up preferring the 'lite' look.

Maybe tonight, maybe tomorrow - got some other stuff to do, so time may be against me today.
FD22
Vic 20 Hobbyist
Posts: 148
Joined: Mon Feb 15, 2010 12:31 pm

Post by FD22 »

OK, finally got a chance to finish this; it's not optimised as far as I'd like as it still occupies 407 bytes and I'm certain I can reduce that. But it does now look the way I want it to, and includes a 'top-of-stack' dump:

Image

Get the code here:
http://vicdev.googlecode.com/files/bsod.6502
http://vicdev.googlecode.com/files/VICMap.6502

I'll post an optimised version in a day or two.
Kananga
Vic 20 Afficionado
Posts: 317
Joined: Mon Mar 08, 2010 2:11 pm

Post by Kananga »

cool! I like the "?BROKEN SOFTWARE" error... :)
Buy the new Bug-Wizard, the first 100 bugs are free!
FD22
Vic 20 Hobbyist
Posts: 148
Joined: Mon Feb 15, 2010 12:31 pm

Post by FD22 »

NOTE: I've just realised the code is broken somewhere in the display logic for .SR - you can see in the screenshot above that the flag bit settings are shown correctly, but the register value is showing as '00'. I think this is an incorrect memory label reference in a later part of the code which deals with the stack dump, as it was working fine before I finalised that.

It's probably a five-minute fix, but I've been off the grid for a week and haven't had a chance to get to it - I'll post a new version later today.
FD22
Vic 20 Hobbyist
Posts: 148
Joined: Mon Feb 15, 2010 12:31 pm

Post by FD22 »

OK, fixed the silly bug (it was, in fact, an incorrect label reference as I suspected). I've also shaved off some code size, memory consumption and clock cycles, so it now executes with minimal Zero Page requirement, and in a total of 377 bytes.

The main BSOD code is here:
http://vicdev.googlecode.com/files/bsod.6502

It needs these two little helper subroutines:
http://vicdev.googlecode.com/files/dec2hex.6502
http://vicdev.googlecode.com/files/petscii.6502

And of course the VIC memory map data definitions:
http://vicdev.googlecode.com/files/VICMap.6502

Sample to show it working:

Code: Select all

					; Assemble for 6502 CPU
					PROCESSOR 6502

					INCLUDE "VICMap.6502"

					lda #<bsod
					sta BRKVEC
					lda #>bsod
					sta BRKVEC+1

					brk
					rts

					; Subroutines
					INCLUDE "bsod.6502"
					INCLUDE "dec2hex.6502"
					INCLUDE "petscii.6502"
Post Reply