6502.org Forum  Projects  Code  Documents  Tools  Forum
It is currently Fri Sep 20, 2024 1:42 pm

All times are UTC




Post new topic Reply to topic  [ 20 posts ]  Go to page 1, 2  Next
Author Message
PostPosted: Sun Mar 03, 2019 10:13 am 
Offline
User avatar

Joined: Thu Dec 11, 2008 1:28 pm
Posts: 10938
Location: England
This thread is for anyone who wants to tackle, share, or discuss solutions to the exercises suggested over in this other thread:

Anyone really wanting to get the benefit of those exercises is encouraged to tackle their own solutions - and usually multiple solutions will be possible - before reading other people's efforts.

(For me, these exercises are not intended to be puzzles, or programming challenges, but exercises which help the programmer explore and understand the features and quirks of the 6502. You can't get fit by watching other people exercise!)

(Prompted by this:
drogon wrote:
Maybe we ought to start to provide solutions ;-)
-Gordon

)


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 12:44 pm 
Offline
User avatar

Joined: Wed Feb 14, 2018 2:33 pm
Posts: 1467
Location: Scotland
Arlet wrote:
Assuming a UART "PutChar" routine, write a routine to output a hexadecimal nibble, and then a routine to output a hexadecimal byte.


Some forums have a hidden "spoiler" facility, but I can't find one here, however, here is my hex print code taken directly from my monitor. A few notes:

  • It's assembled using ca65 but ought to be easy to read or port to other assemblers.
  • My "bios" code considers X & A to be volatile and Y to be precious - obviously other monitor/OS/IO subroutines may handle this differently depending on the environment
  • These are also "underscore" versions as they're all vectored via a fixed-address table that's part of my little monitor/OS, so ordinary code would normally:
    Code:
    jsr oHex4
  • This is my style of coding - I like lower case and this level of indentation. I've also added a few more comments that I might normally.

This is what I consider to be the "cheaty" (or easy) way to do it as it uses a look-up table. The alternative might be to compare for 0-9 or 11-15 then add on '0' or ('A'-10) before printing. If that way saved up to 16 bytes (ie. the lookup table) and I was desperate to save space then I'd probably do it that way.

Code:
;********************************************************************************
; oHex4: oHex8:
;       Output the A register as 1 or 2 hex digits
; This work is granted to the public domain by the creator. See:
;     https://creativecommons.org/publicdomain/
;********************************************************************************

.proc   oHex
.export _oHex8
_oHex8:
        pha                     ; Temp. save
        lsr     a               ; A := A >> 4
        lsr     a
        lsr     a
        lsr     a
        jsr     _oHex4          ; Print top 4 bits as hex
        pla                     ; Restore A and fall into ...

.export _oHex4
_oHex4:
        and     #$0F            ; Isolate bottom 4 bits
        tax     
        lda     hexTable,x
        jmp     putchar         ; and return

hexTable:       .byte   "0123456789ABCDEF"

.endproc


Enjoy,

-Gordon

_________________
--
Gordon Henderson.
See my Ruby 6502 and 65816 SBC projects here: https://projects.drogon.net/ruby/


Last edited by drogon on Sun Mar 03, 2019 4:29 pm, edited 1 time in total.

Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 1:40 pm 
Offline

Joined: Mon Sep 17, 2018 2:39 am
Posts: 136
Hi!

drogon wrote:
Arlet wrote:
Assuming a UART "PutChar" routine, write a routine to output a hexadecimal nibble, and then a routine to output a hexadecimal byte.


Code:
;********************************************************************************
; oHex4: oHex8:
;       Output the A register as 1 or 2 hex digits
;********************************************************************************

.proc   oHex
.export _oHex8
_oHex8:
        pha                     ; Temp. save
        lsr     a               ; A := A >> 4
        lsr     a
        lsr     a
        lsr     a
        jsr     _oHex4          ; Print top 4 bits as hex
        pla                     ; Restore A and fall into ...

.export _oHex4
_oHex4:
        and     #$0F            ; Isolate bottom 4 bits
        tax     
        lda     hexTable,x
        jmp     putchar         ; and return

hexTable:       .byte   "0123456789ABCDEF"

.endproc


Enjoy,

-Gordon


From my own monitor, similar to above, but using decimal mode (shorter code) and keeping X/Y unchanged and ending in a branch instead of jump (this could also be added to your code):

Code:
.proc print_hex
        pha
        lsr
        lsr
        lsr
        lsr
        jsr     hex_digit
        pla
        and     #$0F
.endproc                        ; Fall through
.proc hex_digit
        sed                     ; set decimal mode
        cmp     #$0A            ; set carry for +1 if >9
        adc     #'0'            ; add ASCII "0"
        cld                     ; clear decimal mode
        bne put_char            ; jump always!
.endproc


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 1:49 pm 
Offline
User avatar

Joined: Tue Mar 05, 2013 4:31 am
Posts: 1382
Seems we all have similar routines... here's a couple from my Monitor code that does the same:

Code:
;PRBYTE subroutine: Converts a single Byte to 2 HEX ASCII characters and sends to console on
; entry, A reg contains the Byte to convert/send. Register contents are preserved on entry/exit.
PRBYTE          PHA                     ;Save A register
                PHY                     ;Save Y register
PRBYT2          JSR     BIN2ASC         ;Convert A reg to 2 ASCII Hex characters
                JSR     B_CHROUT        ;Print high nibble from A reg
                TYA                     ;Transfer low nibble to A reg
                JSR     B_CHROUT        ;Print low nibble from A reg
                PLY                     ;Restore Y Register
                PLA                     ;Restore A Register
                RTS                     ;And return to caller
;


Code:
;BIN2ASC subroutine: Convert single byte to two ASCII HEX digits
; Enter: A register contains byte value to convert
; Return: A register = high digit, Y register = low digit
BIN2ASC         PHA                     ;Save A Reg on stack
                AND     #$0F            ;Mask off high nibble
                JSR     ASCII           ;Convert nibble to ASCII HEX digit
                TAY                     ;Move to Y Reg
                PLA                     ;Get character back from stack
                LSR     A               ;Shift high nibble to lower 4 bits
                LSR     A
                LSR     A
                LSR     A
;
ASCII           CMP     #$0A            ;Check for 10 or less
                BCC     ASOK            ;Branch if less than 10
                CLC                     ;Clear carry for addition
                ADC     #$07            ;Add $07 for A-F
ASOK            ADC     #$30            ;Add $30 for ASCII
                RTS                     ;Return to caller
;


37 bytes in total for both routines. A third routine is used to print a word value:

Code:
;PRWORD subroutine: Converts a 16-bit word to 4 HEX ASCII characters and sends to console. On
; entry, A reg contains High Byte, Y reg contains Low Byte. Register are preserved on entry/exit.
PRWORD          PHA                     ;Save A register
                PHY                     ;Save Y register
                JSR     PRBYTE          ;Convert and print one HEX character (00-FF)
                TYA                     ;Get Low byte value
                BRA     PRBYT2          ;Finish up Low Byte and exit
;


This adds another 8 bytes for a total of 45 bytes.

_________________
Regards, KM
https://github.com/floobydust


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 2:05 pm 
Offline
User avatar

Joined: Wed Feb 14, 2018 2:33 pm
Posts: 1467
Location: Scotland
Nice use of decimal mode up there. It's a mode I've essentially 'deleted' from my 6502 ken, never thinking I might have a use for it.

Due to a (self imposed) design constraint, I can't branch to putchar in my code because I want all IO to go via the vectors which can be re-diected, if required. It might never happen in my code, but you never know - things like the ability to re-direct character IO was used extensively in the Apple II DOS and in the BBC Micro, so I thought why not.

Other interesting things (well, to-me, at least!) is the choice of preserving registers, or not.

Cheers,

-Gordon

_________________
--
Gordon Henderson.
See my Ruby 6502 and 65816 SBC projects here: https://projects.drogon.net/ruby/


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 2:21 pm 
Offline

Joined: Mon Sep 17, 2018 2:39 am
Posts: 136
Hi!

floobydust wrote:
Seems we all have similar routines... here's a couple from my Monitor code that does the same:

Code:
;
ASCII           CMP     #$0A            ;Check for 10 or less
                BCC     ASOK            ;Branch if less than 10
                CLC                     ;Clear carry for addition
                ADC     #$07            ;Add $07 for A-F
ASOK            ADC     #$30            ;Add $30 for ASCII
                RTS                     ;Return to caller
;



Here you can skip the CLC and simply add #6, two cycles and one byte less.


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 2:57 pm 
Offline

Joined: Mon Sep 17, 2018 2:39 am
Posts: 136
Hi!

drogon wrote:
Nice use of decimal mode up there. It's a mode I've essentially 'deleted' from my 6502 ken, never thinking I might have a use for it.


It is from my Atari 8-bit background, there decimal mode is used a lot (in the O.S. math-pack), so it is essential to know it :)


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 3:21 pm 
Offline
User avatar

Joined: Tue Mar 05, 2013 4:31 am
Posts: 1382
I agree on the nice use of decimal mode. like Gordon, I don't use it... but having just checked the WDC W65C02 datasheet, seems that decimal mode is reset (turned off) for Reset and Interrupts, so I could use this in my routine as well.

Also good call on removing the CLC and changing to ADC #$06 instead.

So, in the spirit of having some nice routines, here's one that does the inverse, i.e., takes two ASCII hex characters and returns a single binary byte value ($00-$FF).

Code:
;ASC2BIN subroutine: Convert 2 ASCII HEX digits to a binary (byte) value
; Enter: A register = high digit, Y register = low digit
; Return: A register = binary value
ASC2BIN         JSR     BINARY          ;Convert high digit to 4-bit nibble
                ASL     A               ;Shift to high nibble
                ASL     A
                ASL     A
                ASL     A
                STA     TEMP1           ;Store it in temp area
                TYA                     ;Get Low digit
                JSR     BINARY          ;Convert low digit to 4-bit nibble
                ORA     TEMP1           ;OR in the high nibble
RESERVED        RTS                     ;Return to caller
;
BINARY          SEC                     ;Set carry for subtraction
                SBC     #$30            ;Subtract $30 from ASCII HEX digit
                CMP     #$0A            ;Check for result < 10
                BCC     BNOK            ;Branch if 0-9
                SBC     #$07            ;Else, subtract 7 for A-F
BNOK            RTS                     ;Return to caller
;


26 bytes total, using one byte in Page Zero for TEMP1.

_________________
Regards, KM
https://github.com/floobydust


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 4:16 pm 
Offline

Joined: Sat Dec 13, 2003 3:37 pm
Posts: 1004
I'm going to get all pedantic here. These are all well and good, but just to note -- none of this code is licensed (beyond sole copyright of the owners). And folks, in theory, "can't use any of it" if they were looking for code to use.

I don't know if the forum has a blanket license on source code published in the topics or not.


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 4:19 pm 
Offline

Joined: Mon May 21, 2018 8:09 pm
Posts: 1462
Moving on to another exercise, let's explore some methods of filling 1000 bytes with zero. The 6502 can only count up to 256 in one register, so we must first convert 1000 decimal to 3*256 + 232. Let's assume we're filling memory from $7C00 (which corresponds to the Mode 7 framebuffer on the BBC Micro, which occupies 1000 bytes for a 40x25 character matrix).

One fast 65C02 solution using unrolled loops:
Code:
   LDX #232
L1:
   DEX
   STZ $7F00,X
   BNE L1
L2:
   DEX
   STZ $7E00,X
   STZ $7D00,X
   STZ $7C00,X
   BNE L2
This is 20 bytes of code and requires no zero-page locations. Filling 1024 bytes would, ironically, take less code and possibly less time, as only the second loop would be required.

Attempting a more general (but bigger and slower) solution:
Code:
   ; Start address ($7C00)
   LDX #$7C
   STX $81
   STZ $80
   ; Byte count (1000), with outer loop counter incremented for fencepost reasons
   LDY #232
   LDX #4
   ; Byte to store
   LDA #0
L1:
   ; Store a zero and increment pointer
   ; there's no STZ (zp) unfortunately…
   STA ($80)
   INC $80
   BNE O1
   INC $81
O1:
   ; Decrement counter and check for completion
   DEY
   BNE L1
   DEX
   BNE L1
The 14-byte section starting at L1: can be extracted to make a general memset() subroutine which expects $80-$81 and the registers to be pre-filled with parameters. It is however a lot slower than the specialised, unrolled version at top.


Last edited by Chromatix on Mon Mar 04, 2019 12:04 am, edited 1 time in total.

Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 4:40 pm 
Offline
User avatar

Joined: Wed Feb 14, 2018 2:33 pm
Posts: 1467
Location: Scotland
whartung wrote:
I'm going to get all pedantic here. These are all well and good, but just to note -- none of this code is licensed (beyond sole copyright of the owners). And folks, in theory, "can't use any of it" if they were looking for code to use.

I don't know if the forum has a blanket license on source code published in the topics or not.


A good point and one that's been the subject of debate here in the past, AIUI.

I have amended my submission to the effect of granting the "CC0" attribution to it. See https://creativecommons.org/publicdomain/ and https://wiki.creativecommons.org/wiki/CC0_FAQ

I often use the GPLv3 or LGPLv3 licenses for projects I publish though, however for short extracts like the above, I think that CC0 is just fine. It's really fairly generic code.

It would probably be a bit of a minefield to blanket cover the forums with e.g. CC0 (or whatever) though, however it may be possible to add/assume it for new original code snippets made from a certain date in the (near) future - to allow time for people to like/dislike/debate it. It may require messaging all forum users, putting big banners up something along the lines of "unless you say otherwise, all code snippets are assumed to be published under CC0" (or whatever).

-Gordon

_________________
--
Gordon Henderson.
See my Ruby 6502 and 65816 SBC projects here: https://projects.drogon.net/ruby/


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 5:15 pm 
Offline

Joined: Mon May 21, 2018 8:09 pm
Posts: 1462
For trivial exercise answers like the ones in this thread, which are implicitly meant to be educational anyway, I don't think there's a problem with copyright.


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 6:04 pm 
Offline
User avatar

Joined: Wed Feb 14, 2018 2:33 pm
Posts: 1467
Location: Scotland
On the zero 1000 bytes front, my 6502 solution is not significantly different from that presented by Chromatix, (although I tend to use ZP more than the 2-register count there), so I did it in Sweet16 - possibly not in the true spirit of 6502 code, but it is present in Apple II's and I'm using it in my little SBC, so...

Code:
; CC0 license.
.export fill1000
.proc   fill1000

        jsr     strout
        .byte   "Fill 1000",13,10,0

        goSweet16
        sub     r0              ; Set r0 to zero
        set     r1,$5000        ; Start address
        set     r2,1000         ; Bytes to fill
fill:   std     @r1             ; Store double (2 bytes) from r0 @r1; r1 += 2
        dcr     r2
        dcr     r2
        bnz     fill
        exSweet16

        rts
.endproc


and a test run by firstly filling RAM with $AA, then checking:

Code:
% 4ff0.5400
4FF0: AA AA AA AA AA AA AA AA  |          |
4FF8: AA AA AA AA AA AA AA AA  |          |
5000: AA AA AA AA AA AA AA AA  |          |
5008: AA AA AA AA AA AA AA AA  |          |
...
53E0: AA AA AA AA AA AA AA AA  |          |
53E8: AA AA AA AA AA AA AA AA  |          |
53F0: AA AA AA AA AA AA AA AA  |          |
53F8: AA AA AA AA AA AA AA AA  |          |
5400: AA AA AA AA AA AA AA AA  |          |


run the code, and check again:
Code:
% r

Fill 1000
% 4ff0.5400
4FF0: AA AA AA AA AA AA AA AA  |          |
4FF8: AA AA AA AA AA AA AA AA  |          |
5000: 00 00 00 00 00 00 00 00  |          |
5008: 00 00 00 00 00 00 00 00  |          |
...
53D8: 00 00 00 00 00 00 00 00  |          |
53E0: 00 00 00 00 00 00 00 00  |          |
53E8: AA AA AA AA AA AA AA AA  |          |
53F0: AA AA AA AA AA AA AA AA  |          |
53F8: AA AA AA AA AA AA AA AA  |          |
5400: AA AA AA AA AA AA AA AA  |          |


I've snipped lots of duplicate lines of output. Also note the goSweet16 and exSweet16 are macros that enter sweet16 mode (jsr sweet16) and an assembler directive to assemble sweet16 opcodes, and the reverse.

It's 17 bytes of code including the jsr and rts, obviously much slower than native 6502 though, but if desperate, I could save a byte by changing the std into st to store a single byte, then only one dcr needed. It would be a little slower that way.

Cheers,

-Gordon

-edit to say-
Ps. Just realised I can save that byte anyway, since we'r filing 1000 bytes, half that is 500, so set r2, 500 and remove one of the dcr's.

_________________
--
Gordon Henderson.
See my Ruby 6502 and 65816 SBC projects here: https://projects.drogon.net/ruby/


Last edited by drogon on Sun Mar 03, 2019 7:14 pm, edited 1 time in total.

Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 6:54 pm 
Offline
User avatar

Joined: Thu Dec 11, 2008 1:28 pm
Posts: 10938
Location: England
Thanks for showing your tests - an out-by-one error is very easy when every loop is hand-built.


Top
 Profile  
Reply with quote  
PostPosted: Sun Mar 03, 2019 8:39 pm 
Offline
User avatar

Joined: Tue Mar 05, 2013 4:31 am
Posts: 1382
While there have been numerous routines for filling, moving and comparing memory, I eventually integrated all of these into a single set of routines. I later added the programming of the Atmel EEPROM into this as well. Granted, it's not going to be as fast as some other dedicated routines, but one of the goals was to make it flexible and relatively small in memory size. The Copy/Fill/Move functions all enter at the CPMVFL label, while the Program EEPROM enters at the PROGEE label.

Code:
;[C] Compare routine: one memory range to another and display any addresses which do not match
;[M] Move routine: uses this section for parameter input, then branches to MOVER below
;[F] Fill routine: uses this section for parameter input but requires a fill byte value
;[CTRL-P] Program EEPROM: uses this section for parameter input and to write the EEPROM
;Uses source, target and length input parameters. errors in compare are shown in target space
FM_INPUT        LDA     #$05            ;Send "val: " to terminal
                JSR     HEX2            ;Use short cut version for print and input
                TAX                     ;Xfer fill byte to X reg
                JSR     CONTINUE        ;Handle continue prompt
;
;Memory fill routine: parameter gathered below with Move/Fill,
; then a jump to here Xreg contains fill byte value
FILL_LP         LDA     LENL            ;Get length low byte
                ORA     LENH            ;OR in length high byte
                BEQ     DONEFILL        ;Exit if zero
                TXA                     ;Get fill byte
                STA     (TGTL)          ;Store in target location
                JSR     UPD_TL          ;Update Target/Length pointers
                BRA     FILL_LP         ;Loop back until done
;
;Compare/Move/Fill memory operations enter here, branches as required
CPMVFL          STA     TEMP2           ;Save command character
                JSR     B_CHROUT        ;Print command character (C/M/F)
                CMP     #$46            ;Check for F - fill memory
                BNE     PRGE_E          ;If not continue normal parameter input
                LDA     #$03            ;Get msg " addr:"
                BRA     F_INPUT         ;Branch to handle parameter input
;
;EEPROM write operation enters here
PROGEE          LDA     #$21            ;Get PRG_EE msg
                JSR     PROMPT          ;send to terminal
                STZ     TEMP2           ;Clear (Compare/Fill/Move) / error flag
;
PRGE_E          LDA     #$06            ;Send " src:" to terminal
                JSR     HEX4            ;Use short cut version for print and input
                STA     SRCL            ;Else, store source address in variable SRCL,SRCH
                STY     SRCH            ;Store high address
                LDA     #$07            ;Send " tgt:" to terminal
F_INPUT         JSR     HEX4            ;Use short cut version for print and input
                STA     TGTL            ;Else, store target address in variable TGTL,TGTH
                STY     TGTH            ;Store high address
                LDA     #$04            ;Send " len:" to terminal
                JSR     HEX4            ;Use short cut version for print and input
                STA     LENL            ;ELSE, store length address in variable LENL,LENH
                STY     LENH            ;Store high address
;
; All input parameters for Source, Target and Length entered
                LDA     TEMP2           ;Get Command character
                CMP     #$46            ;Check for fill memory
                BEQ     FM_INPUT        ;Handle the remaining input
                CMP     #$43            ;Test for Compare
                BEQ     COMPLP          ;Branch if yes
                CMP     #$4D            ;Check for Move
                BEQ     MOVER           ;Branch if yes
;
PROG_EE         LDA     #$22            ;Get warning msg
                JSR     PROMPT          ;Send to console
                JSR     CONTINUE2       ;Prompt for y/n
;
;Programming of the EEPROM is now confirmed by user. This routine will copy the core move and test
; routine from ROM to RAM, then call COMPLP to write and compare. As I/O can generate interrupts
; which point to ROM routines, all interrupts must be disabled during the program sequence.
;
;Send message to console for writing EEPROM
                LDA     #$23            ;Get write message
                JSR     PROMPT          ;Send to console
OC_LOOP         LDA     OCNT            ;Check output buffer count
                BNE     OC_LOOP         ;Loop back until buffer sent
;
;Xfer byte write code to RAM for execution
                JSR     XFER_BYTE_WRT   ;Xfer byte write code to Page Zero
;
;Wait for 1/2 second for RAM/ROM access to settle
                LDA     #$32            ;Set milliseconds to 50(*10 ms)
                JSR     B_SET_DLY       ;Set Delay parameters
                JSR     B_EXE_MSDLY     ;Call delay for 1/2 second
;
PROG_EEP        SMB7    TEMP2           ;Set EEPROM write active mask
                JSR     COMPLP          ;Call routine to write/compare
                BBR6    TEMP2,PRG_GOOD  ;Skip down if no error
                LDA     #$25            ;Get Prog failed message
                BRA     BRA_PRMPT       ;Branch to Prompt routine
;
PRG_GOOD        LDA     #$24            ;Get completed message
BRA_PRMPT       JMP     PROMPT          ;Send to console and exit
;
COMPLP          LDA     LENL            ;Get low byte of length
                ORA     LENH            ;OR in High byte of length
                BEQ     QUITMV          ;If zero, nothing to compare/write
                BBR7    TEMP2,SKP_BURN  ;Skip burn if bit 7 clear
                JSR     BURN_BYTE       ;Else Burn a byte to EEPROM
SKP_BURN        LDA     (SRCL)          ;Else load source
                CMP     (TGTL)          ;Compare to source
                BEQ     CMP_OK          ;If compare is good, continue
;
                SMB6    TEMP2           ;Set bit 6 of TEMP2 flag (compare error)
                JSR     SPC2            ;Send 2 spaces
                JSR     DOLLAR          ;Print $ sign
                LDA     TGTH            ;Get high byte of address
                LDY     TGTL            ;Get Low byte of address
                JSR     PRWORD          ;Print word
                JSR     SPC             ;Add 1 space for formatting
;
CMP_OK          JSR     UPD_STL         ;Update pointers
                BRA     COMPLP          ;Loop back until done
;
;Parameters for move memory entered and validated, now make decision on which direction
; to do the actual move, if overlapping, move from end to start, else from start to end.
MOVER           JSR     CONTINUE        ;Prompt to continue move
                SEC                     ;Set carry flag for subtract
                LDA     TGTL            ;Get target lo byte
                SBC     SRCL            ;Subtract source lo byte
                TAX                     ;Move to X reg temporarily
                LDA     TGTH            ;Get target hi byte
                SBC     SRCH            ;Subtract source hi byte
                TAY                     ;Move to Y reg temporarily
                TXA                     ;Xfer lo byte difference to A reg
                CMP     LENL            ;Compare to lo byte length
                TYA                     ;Xfer hi byte difference to A reg
                SBC     LENH            ;Subtract length lo byte
                BCC     RIGHT           ;If carry is clear, overwrite condition exists
;Move memory block first byte to last byte, no overlap condition
MVNO_LP         LDA     LENL            ;Get length low byte
                ORA     LENH            ;OR in length high byte
                BEQ     QUITMV          ;Exit if zero bytes to move
                LDA     (SRCL)          ;Load source data
                STA     (TGTL)          ;Store as target data
                JSR     UPD_STL         ;Update Source/Target/Length variables
                BRA     MVNO_LP         ;Branch back until length is zero
;
;Move memory block last byte to first byte avoids overwrite in source/target overlap
RIGHT           LDX     LENH            ;Get the length hi byte count
                CLC                     ;Clear carry flag for add
                TXA                     ;Xfer High page to A reg
                ADC     SRCH            ;Add in source hi byte
                STA     SRCH            ;Store in source hi byte
                CLC                     ;Clear carry for add
                TXA                     ;Xfer High page to A reg
                ADC     TGTH            ;Add to target hi byte
                STA     TGTH            ;Store to target hi byte
                INX                     ;Increment high page value for use below in loop
                LDY     LENL            ;Get length lo byte
                BEQ     MVPG            ;If zero no partial page to move
                DEY                     ;Else, decrement page byte index
                BEQ     MVPAG           ;If zero, no pages to move
MVPRT           LDA     (SRCL),Y        ;Load source data
                STA     (TGTL),Y        ;Store to target data
                DEY                     ;Decrement index
                BNE      MVPRT          ;Branch back until partial page moved
MVPAG           LDA     (SRCL),Y        ;Load source data
                STA     (TGTL),Y        ;Store to target data
MVPG            DEY                     ;Decrement page count
                DEC     SRCH            ;Decrement source hi page
                DEC     TGTH            ;Decrement target hi page
                DEX                     ;Decrement page count
                BNE     MVPRT           ;Loop back until all pages moved
QUITMV          RTS                     ;Return to caller
;
;Xfer byte write code to RAM for execution
XFER_BYTE_WRT   LDX     #BYTE_WRE-BYTE_WRS+1 ;Get length of byte write code
BYTE_XFER       LDA     BYTE_WRS-1,X    ;Get code
                STA     BURN_BYTE-1,X   ;Write code to RAM
                DEX                     ;Decrement index
                BNE     BYTE_XFER       ;Loop back until done
                RTS                     ;Return to caller
;
BYTE_WRS        SEI                     ;Disable interrupts
                LDA     (SRCL)          ;Get source byte
                STA     (TGTL)          ;Write to target byte
                LDA     (TGTL)          ;Read target byte (EEPROM)
                AND     #%01000000      ;Mask off bit 6 - toggle bit
BYTE_WLP        STA     TEMP3           ;Store in Temp location
                LDA     (TGTL)          ;Read target byte again (EEPROM)
                AND     #%01000000      ;Mask off bit 6 - toggle bit
                CMP     TEMP3           ;Compare to last read (toggles if write mode)
                BNE     BYTE_WLP        ;Branch back if not done
                CLI                     ;Re-enable interrupts
BYTE_WRE        RTS                     ;Return to caller
;


The other support routines are here:

Code:
;Routines to update pointers for memory operations. UPD_STL subroutine: Increments Source
; and Target pointers. UPD_TL subroutine: Increments Target pointers only, then drops into
; decrement Length pointer. Used by multiple Memory operation commands.
UPD_STL         INC     SRCL            ;Increment source low byte
                BNE     UPD_TL          ;Check for rollover
                INC     SRCH            ;Increment source high byte
UPD_TL          INC     TGTL            ;Increment target low byte
                BNE     DECLEN          ;Check for rollover
                INC     TGTH            ;Increment target high byte
;
;DECLEN subroutine: decrement 16-bit variable LENL/LENH
DECLEN          LDA     LENL            ;Get length low byte
                BNE     SKP_LENH        ;Test for LENL = zero
                DEC     LENH            ;Else decrement length high byte
SKP_LENH        DEC     LENL            ;Decrement length low byte
                RTS                     ;Return to caller
;


There's a few other routines for confirming the write (JSR CONTINUE, JSR HEX, JSR PROMPT, etc.) and for printing mismatched locations on Compare (JSR PRWORD) but overall, it's not too bad considering everything it does, 302 bytes for the above.

_________________
Regards, KM
https://github.com/floobydust


Top
 Profile  
Reply with quote  
Display posts from previous:  Sort by  
Post new topic Reply to topic  [ 20 posts ]  Go to page 1, 2  Next

All times are UTC


Who is online

Users browsing this forum: No registered users and 21 guests


You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot post attachments in this forum

Search for:
Jump to: