A sample debugging session with MINIMON

Basic and Machine Language

Moderator: Moderators

User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

That’s a great idea, but I’ll have to rearrange the flow a bit. I’d like to shave off enough bytes (7, I think) to fit both the generator and knapsack data in the cassette buffer.
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

Mike wrote: Fri Jul 24, 2020 12:55 am The tail of your routine could probably be shorted like thus:
Your technique provided enough of a savings so that I could fit the knapsack AND generator in the cassette buffer!

I also realized that I could combine the two three-byte tests into one, and two two-byte tests into one, so it's even shorter.

Code: Select all

; Code Instrumention Generator
;
; Create a breakpoint at the specified address, and a code knapsack.
; If there's already a breakpoint set, clear it and restore
; the code.
;
; (Originally assembled with xa)

*=$033c

; BASIC Routine
UND_ERROR   = $c8e3             ; UNDEF'D STATEMENT ERROR

; Knapsack Generator
;KNAPSACK   = A 13-byte region after the generator code
EFADDR      = $07               ; Temp zeropage pointer to breakpoint address
BREAKPT     = KNAPSACK+10       ; Breakpoint address (2 bytes)
KNAPSIZE    = BREAKPT+2         ; Knapsack size (1 byte)

; Main routine entry point
; If no breakpoint is set, set one by setting X as the low byte
; and A as the high byte.
;
; If a breakpoint is already set, then clear it by restoring the knapsack code
Main:       ldy KNAPSIZE        ; If a breakpoint is not already set, then
            beq NewKnap         ;   create it with the address at Y/X
restore:    lda BREAKPT         ; Otherwise, restore the breakpoint to the
            sta EFADDR          ;   original code by copying the
            lda BREAKPT+1       ;   bytes in the knapsack back to the code
            sta EFADDR+1        ;   ,,
            dey
-loop       lda KNAPSACK+2,y    ; Move between 3 and 5 bytes back
            sta (EFADDR),y      ;   to their original locations
            dey                 ;   ,,
            bpl loop            ;   ,,
            lda #$00            ; Reset the knapsack size so that doing it again
            sta KNAPSIZE        ;   doesn't mess up the original code
restore_r:  rts                 ;   ,,

; New Knapsack
; Generate a new knapsack at the address specified by X (low byte) and
; A (high byte)
NewKnap:    stx EFADDR          ; Save low byte of breakpoint
            sta EFADDR+1        ; Save high byte of breakpoint
            ldy #$00
next_inst:  tya                 ; Preserve Y against SizeOf
            pha                 ; ,,
            lda (EFADDR),y      ; A = Opcode of the breakpoint instruction
            jsr SizeOf          ; X = Size of instruction (1-3)
            bne inst_ok         ; Error if relative branch instruction
            jmp UND_ERROR       ; ?UNDEF'D STATEMENT ERROR     
inst_ok:    pla
            tay
-loop:      lda (EFADDR),y      ; Move X bytes starting at Y index
            sta KNAPSACK+2,y    ; ,,
            iny                 ; ,, (Y is a running count of knapsacked bytes)
            dex                 ; ,,
            bne loop            ; ,,
            cpy #$03            ; If at least three bytes have been knapsacked
            bcc next_inst       ;   we're done
            lda EFADDR          ; Stash pointer in breakpoint storage for
            sta BREAKPT         ;   later restoration
            lda EFADDR+1        ;   ,,
            sta BREAKPT+1       ;   ,,
            sty KNAPSIZE        ; Save knapsack size for later
            lda #$ea            ; (NOP)
-loop:      cpy #$03            ; Pad code with more than three bytes with
            beq add_kjmp        ;   NOPs after the first three
            dey                 ;   ,,
            sta (EFADDR),y      ;   ,,
            bne loop            ;   ,,
add_kjmp:   ldy #$00
            lda #$4c            ; (JMP) This is the JMP to the knapsack
            sta (EFADDR),y      ; 
            lda #<KNAPSACK      ; Store knapsack JMP low byte
            iny                 ; ,,
            sta (EFADDR),y      ; ,,
            lda #>KNAPSACK      ; Store knapsack JMP high byte
            iny                 ; ,,
            sta (EFADDR),y      ; ,,
            lda KNAPSIZE        ; Calculate the return jump point (original
            tay                 ;   address + Y)
            clc                 ;   ,,
            adc EFADDR          ;   ,,
            sta KNAPSACK+3,y    ; Store return JMP low byte
            lda #$00
            adc EFADDR+1 
            sta KNAPSACK+4,y    ; Store return JMP high byte
            lda #$4c            ; (JMP) This is the JMP to the return point        
            sta KNAPSACK+2,y    ; ,,
            rts
    
; Size Of Instruction
; Given an opcode in A, return instruction size in X
; Set Z if the instruction is a branch   
SizeOf:     ldx #3              ; X is number of bytes in instruction
            cmp #$20            ; JSR...
            beq three           ;   "THERE... ARE... THREE... BYTES!" --Picard
            tay                 ; Save opcode in Y for repeated testing
            and #%00001000      ; ????0??? usually means two bytes
            beq two_cand        ; ,,
            tya                 ; The pattern ?????010 always means one byte
            and #%00000101      ;   when the two-byte test above fails
            beq one             ;   ,,
            tya                 ; If the previous tests fail, this pattern
            and #%00010100      ;   always indiates three bytes. Really testing
            bne three           ;   for ???11??? and ????11??
two_cand:   tya                 ; Of the two-byte instructions that match
            and #%10011111      ;   ????0000, all of them have either bit 4 or
            bne two             ;   bit 7 set. If that's not the case, it's 1
one:        dex
two:        dex
three:      tya                 ; If the instruction low nybble is 0, and bit 4
            and #$1f            ;   is set, it's a branch, so set Z
            cmp #$10            ;   ,,
size_r:     rts

KNAPSACK:   .byte $00,$ea,0,0,0,0,0,0,0,0,0,0,0 ; BRK,NOP,etc.
Here's the test data generated from wAx's instruction table. A length of 0 here indicates that it's not an official 6502 instruction*. This can be used to verify that SizeOf's results are correct.

Code: Select all

00000000: 01 02 00 00 00 02 02 00 01 02 01 00 00 03 03 00  ................
00000010: 02 02 00 00 00 02 02 00 01 03 00 00 00 03 03 00  ................
00000020: 03 02 00 00 02 02 02 00 01 02 01 00 03 03 03 00  ................
00000030: 02 02 00 00 00 02 02 00 01 03 00 00 00 03 03 00  ................
00000040: 01 02 00 00 00 02 02 00 01 02 01 00 03 03 03 00  ................
00000050: 02 02 00 00 00 02 02 00 01 03 00 00 00 03 03 00  ................
00000060: 01 02 00 00 00 02 02 00 01 02 01 00 03 03 03 00  ................
00000070: 02 02 00 00 00 02 02 00 01 03 00 00 00 03 03 00  ................
00000080: 00 02 00 00 02 02 02 00 01 00 01 00 03 03 03 00  ................
00000090: 02 02 00 00 02 02 02 00 01 03 01 00 00 03 00 00  ................
000000a0: 02 02 02 00 02 02 02 00 01 02 01 00 03 03 03 00  ................
000000b0: 02 02 00 00 02 02 02 00 01 03 01 00 03 03 03 00  ................
000000c0: 02 02 00 00 02 02 02 00 01 02 01 00 03 03 03 00  ................
000000d0: 02 02 00 00 00 02 02 00 01 03 00 00 00 03 03 00  ................
000000e0: 02 02 00 00 02 02 02 00 01 02 01 00 03 03 03 00  ................
000000f0: 02 02 00 00 00 02 02 00 01 03 00 00 00 03 03 00  ................
* Nobody will be surprised that the illegal opcodes do not follow the patterns I found for official opcodes. Okay, I was a tiny bit surprised.
Last edited by chysn on Sat Jul 25, 2020 3:41 pm, edited 13 times in total.
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

Mike wrote: Fri Jul 24, 2020 12:55 am BRK actually was handled as a two byte instruction.
I just re-read this and I'm trying to absorb it. I get that BRK advances the program counter two bytes, but I can't think of any use of instruction length where treating it as a two-byte instruction makes sense.
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
User avatar
Mike
Herr VC
Posts: 4841
Joined: Wed Dec 01, 2004 1:57 pm
Location: Munich, Germany
Occupation: electrical engineer

Re: A sample debugging session with MINIMON

Post by Mike »

You can save a few more bytes by replacing:

Code: Select all

[...]
three:      clc                 ; Clear carry indicates non-relative mode
            tya 
            and #%00001111      ; If the instruction low nybble is 0, it's a
            bne size_r          ;   branch instruction if and only if bit 4
            tya                 ;   is set. 4xASL so sets Carry, and indicates
            asl                 ;   an instruction that can't be knapsacked
            asl                 ;   ,,
            asl                 ;   ,,
            asl                 ;   ,,
size_r:     rts
with

Code: Select all

[...]
three:      tya                 ; If the instruction low nybble is 0, it's a
            asl                 ;   branch instruction if and only if bit 4
            asl                 ;   is set. 4x ASL so sets Carry from bit 4,
            asl                 ;   Z from the low nibble, and thus indicates
            asl                 ;   an instruction that can't be knapsacked
            beq size_r          ; Possible candidate for branch, retain C.
            clc                 ; Not a candidate, force C=0.
size_r:     rts
:)
Mike wrote:BRK actually was handled as a two byte instruction.
chysn wrote:I just re-read this and I'm trying to absorb it. I get that BRK advances the program counter two bytes, but I can't think of any use of instruction length where treating it as a two-byte instruction makes sense.
The byte after BRK could be used to convey information to the BRK handler, similar to what the TRAP #x instruction does on the 68K. Anyhow, I might have misremembered that, and it's also not really relevant in our use case here: we're unlikely to replace a BRK instruction that's already there with yet another BRK instruction in a knapsack ...
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

Mike wrote: Fri Jul 24, 2020 10:26 am You can save a few more bytes by replacing:

Code: Select all

this
with

Code: Select all

that
:)
Elegant! I made that replacement in the "final" version above. Thanks!
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
User avatar
Mike
Herr VC
Posts: 4841
Joined: Wed Dec 01, 2004 1:57 pm
Location: Munich, Germany
Occupation: electrical engineer

Re: A sample debugging session with MINIMON

Post by Mike »

chysn wrote:Elegant! I made that replacement in the "final" version above. Thanks!
I discussed this with a good friend this evening while dining at the Italian restaurant, and he came up with an even shorter solution to detect the %xxx10000 bit pattern of branch opcodes:

Code: Select all

[...]
 AND #$1F
 CMP #$10
... with the result in the Z flag (Z=1 => branch, Z=0 => no branch) instead.
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

Mike wrote: Fri Jul 24, 2020 3:56 pm
chysn wrote:Elegant! I made that replacement in the "final" version above. Thanks!
I discussed this with a good friend this evening while dining at the Italian restaurant, and he came up with an even shorter solution to detect the %xxx10000 bit pattern of branch opcodes:

Code: Select all

[...]
 AND #$1F
 CMP #$10
... with the result in the Z flag (Z=1 => branch, Z=0 => no branch) instead.
That was actually the first thing I thought of, but my brain then went, "That's exactly as many bytes as 4 ASLs and I still need to set Carry." I don't remember why I was so determined to use Carry besides the fact that I was already using it.

I'll make this update. Thank your friend for me!

But, oh, now that I'm trying implementation, the memories are flooding back. I've got a PLA/TAY after the SizeOf call, which will affect Z before I can check it.
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
User avatar
Mike
Herr VC
Posts: 4841
Joined: Wed Dec 01, 2004 1:57 pm
Location: Munich, Germany
Occupation: electrical engineer

Re: A sample debugging session with MINIMON

Post by Mike »

chysn wrote:But, oh, now that I'm trying implementation, the memories are flooding back. I've got a PLA/TAY after the SizeOf call, which will affect Z before I can check it.
You can re-order (and replace BCC with BNE in due course)

Code: Select all

            jsr SizeOf          ; X = Size of instruction (1-3)
            pla
            tay
            bcc xfer            ; Error if relative branch instruction
            jmp UND_ERROR       ; ?UNDEF'D STATEMENT ERROR     
xfer:       lda (EFADDR),y      ; Move X bytes starting at Y index
to

Code: Select all

            jsr SizeOf          ; X = Size of instruction (1-3)
            bne inst_ok         ; Error if relative branch instruction
            jmp UND_ERROR       ; ?UNDEF'D STATEMENT ERROR     
inst_ok:    pla
            tay
xfer:       lda (EFADDR),y      ; Move X bytes starting at Y index
as calling the error handler of BASIC will clean up the stack anyhow.


Edit: label inst_ok added from your already amended source
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

Mike wrote: Fri Jul 24, 2020 4:34 pm You can re-order (and replace BCC with BNE in due course)
Indeed, that's updated and tested. It's down to 160 bytes, not including the knapsack storage!
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
User avatar
Mike
Herr VC
Posts: 4841
Joined: Wed Dec 01, 2004 1:57 pm
Location: Munich, Germany
Occupation: electrical engineer

Re: A sample debugging session with MINIMON

Post by Mike »

Mike wrote:Regarding the SizeOf subroutine: IIRC, there exists a compact code snippet which derives the instruction length directly from the opcode byte, and which is not bigger than about 2 dozen instructions. Even if the check for branch instructions is added, that routine could be an alternative to hardcoding the address of the instruction decode routine in wAx or MINIMON. As a useful side effect, this makes the knapsack generator stand-alone.
chysn wrote:Update: I wasn't able to find that after a few minutes of Googling, but I've got a lot of 6502 books I can dive into.

Update 2: I think I see the pattern. I'm going to give this a shot... JSR is a weird duck.
Mike wrote:The SizeOf routine I have seen once greatly resembles your version. There it also was noted, that JSR was an oddball regarding the instruction length (i.e. not fitting in the pattern). [...]
I think this is the one I remembered:

https://www.atarimagazines.com/compute/ ... ALYSIS.php

Another one of Jim Butterfield's fame. :wink:

Jim's routine weighs in at 40 bytes - 36 code + 4 data (bitmasks for the BIT instructions) - whereas yours only needs 28 bytes (for the code up to the two DEX instructions), so even if your routine uses Y you can claim to have substantially improved upon Jim's attempt. :)
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

Mike wrote: Tue Sep 15, 2020 5:44 am https://www.atarimagazines.com/compute/ ... ALYSIS.php

...

Jim's routine weighs in at 40 bytes - 36 code + 4 data (bitmasks for the BIT instructions) - whereas yours only needs 28 bytes (for the code up to the two DEX instructions), so even if your routine uses Y you can claim to have substantially improved upon Jim's attempt. :)
Cool, thanks for tracking that down! Later I'll do a side-by-side comparison and see if there's any additional wisdom that will cut the size down even more.
Last edited by chysn on Tue Sep 15, 2020 7:21 am, edited 1 time in total.
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

Mike wrote: Tue Sep 15, 2020 5:44 am https://www.atarimagazines.com/compute/ ... ALYSIS.php

Another one of Jim Butterfield's fame. :wink:
It looks like, aside from treating JSR as the freak that it is, Mr Butterfield and I found different solutions. If I had seen this within a few days of writing mine, I'd still have the patterns dancing in my head, and I'd have been able to more clearly understand the differences. But the general idea is the same, to find paths that eliminate wrong answers. For both of us, the path involves four bit tests (two of our tests are the same, and two are different), and everything else is technique.

His goal was to educate on the use of BIT. Ironically, in trying to sell BIT as more efficient than AND, he's using it in probably the least-efficient way. He's essentially using BIT as a four-byte instruction, which will kill you if the goal is brevity.
User avatar
Mike
Herr VC
Posts: 4841
Joined: Wed Dec 01, 2004 1:57 pm
Location: Munich, Germany
Occupation: electrical engineer

Re: A sample debugging session with MINIMON

Post by Mike »

chysn wrote:He's essentially using BIT as a four-byte instruction, [...]
It would probably have been o.k. if the desired bit-patterns happened to pop up (likely by chance) in the rest of the program. Also, the handling of the X register is rather inefficient in Jim's code, the LDX #$03/.../DEX/DEX structure is somewhat snappier indeed.
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: A sample debugging session with MINIMON

Post by chysn »

Mike wrote: Tue Sep 15, 2020 7:24 am
chysn wrote:He's essentially using BIT as a four-byte instruction, [...]
It would probably have been o.k. if the desired bit-patterns happened to pop up (likely by chance) in the rest of the program. Also, the handling of the X register is rather inefficient in Jim's code, the LDX #$03/.../DEX/DEX structure is somewhat snappier indeed.
Funny you should mention those issues, because I was just finishing this:

Code: Select all

SizeOf:     ldx #3
            cmp #$20
            beq three
            bit $f81d       ; $9f in KERNAL ROM
            beq one
            bit $f11f       ; $08 in KERNAL ROM
            beq two
            bit $f15e       ; $00 in KERNAL ROM
            beq one
            bit $f0e9       ; $16 in KERNAL ROM
            beq two
            rts             ; three
one:        dex
two:        dex
three:      rts
User avatar
Mike
Herr VC
Posts: 4841
Joined: Wed Dec 01, 2004 1:57 pm
Location: Munich, Germany
Occupation: electrical engineer

Re: A sample debugging session with MINIMON

Post by Mike »

chysn wrote:Funny you should mention those issues, because I was just finishing this:

Code: Select all

            bit $f15e       ; $00 in KERNAL ROM
            beq one
That doesn't work as intended, as the branch is always executed.

Here's my version derived from your SizeOf routine - I use values from the BASIC ROM, as that one is less likely to have been replaced *) with another version (PAL and NTSC KERNAL are different, also there's JiffyDOS around):

Code: Select all

.SizeOf
 LDX #$03
 CMP #$20
 BEQ SizeOf_03
 BIT $C3B9      ; #$08 from BASIC ROM 
 BEQ SizeOf_00
 BIT $C01A      ; #$05 from BASIC ROM 
 BEQ SizeOf_01
 BIT $C50E      ; #$14 from BASIC ROM 
 BNE SizeOf_03
.SizeOf_00
 BIT $C01E      ; #$9F from BASIC ROM 
 BNE SizeOf_02
.SizeOf_01
 DEX
.SizeOf_02
 DEX
.SizeOf_03
28 bytes, i.e. same size but it preserves both the A and Y registers. :)


*) my bug-fix of the floating point multiplication routine sits elsewhere, so no problems, either.
Post Reply