📄 s12sermon2r1.dbg
字号:
;* Utility to get a 16-bit value through SCI0 into X
;*********************************************************************
getX: bsr GetChar ;get high byte
tab ;save in B
bsr GetChar ;get low byte
exg a,b ;flip high and low byte
exg d,x ;16-bit value now in IX
rts
;*********************************************************************
;* GetChar - wait indefinitely for a character to be received
;* through SCI0 (until RDRF becomes set) then read char into A
;* and return. Reading character clears RDRF. No error checking.
;*
;* Calling convention:
;* bsr GetChar
;*
;* Returns: received character in A
;*********************************************************************
GetChar: brset SCI0SR1,RDRF,RxReady ;exit loop when RDRF=1
bra GetChar ;loop till RDRF set
RxReady: ldaa SCI0DRL ;read character into A
rts ;return
;*********************************************************************
;* PutChar - sends the character in A out SCI0
;*
;* Calling convention:
;* ldaa data ;character to be sent
;* bsr PutChar
;*
;* Returns: nothing (A unchanged)
;*********************************************************************
PutChar: brclr SCI0SR1,TDRE,PutChar ;wait for Tx ready
staa SCI0DRL ;send character from A
rts
;*********************************************************************
;* CheckModule - check in what memory type the address in IX points to
;* The location may be RAM, FLASH, EEPROM, or a register
;* if the vector table is addresses, IX is changed to point to the
;* same vector in the pseudo vector table
;* returns in B: 1 FLASH or EEPROM
;* 0 RAM or register (all the rest of the address space)
;* -1 access denied (monitor or pseudo vector)
;* all registers are preserved except B
;*********************************************************************
CheckModule: pshd ;preserve original data
cpx #RomStart
blo check4EE ;skip if not flash
cpx #VectorTable
bhs isVector ;is it in the real vector table
cpx #PVecTable
blo isToProgram ;pseudo vector table or monitor area
ldab #$FF ;access denied (N=1, Z=0)
puld ;restore original data (D)
rts
isVector: leax BootStart,x ;access pseudo vector table
bra isToProgram
check4EE: brclr MEMSIZ0,eep_sw1+eep_sw0,isRAM ;Check if device has EEprom
cpx #EEpromStart
blo isRAM ;treat as RAM or registers
cpx #EEpromEnd ;Greater than allocated EE space?
bhi isRAM ;must be registers or RAM
isToProgram: ldab #1 ;set flgs - signal FLASH (N=0, Z=0)
puld ;restore original data (D)
rts
isRAM: clrb ;signal RAM (N=0, Z=1)
puld ;restore original data (D)
rts
;*********************************************************************
;* WriteD2IX - Write the data in D (word) to the address in IX
;* The location may be RAM, FLASH, EEPROM, or a register
;* if FLASH or EEPROM, the operation is completed before return
;* IX and A preserved, returns Z=1 (.EQ.) if OK
;*
;*********************************************************************
WriteD2IX: pshx ;preserve original address
pshd ;preserve original data
bsr CheckModule
bmi ExitWrite ;deny access (monitor or pseudo vector)
beq isRAMword
cpd 0,x ;FLASH or EEPROM needs programming
beq ExitWrite ;exit (OK) if already the right data
pshd ;temp save data to program
tfr x,b ;low byte of target address -> B
bitb #1 ;is B0 = 1?
bne oddAdrErr ;then it's odd addr -> exit
ldd 0,x ;$FFFF if it was erased
cpd #$FFFF ;Z=1 if location was erased first
oddAdrErr: puld ;recover data, don't change CCR
bne ExitWrite ;exit w/ Z=0 to indicate error
bra DoProgram
isRAMword: std 0,x ;write to RAM or register
clra ;force Z=1 to indicate OK
bra ExitWrite
;*********************************************************************
;* WriteA2IX - Write the data in A (byte) to the address in IX
;* The location may be RAM, FLASH, EEPROM, or a register
;* if FLASH or EEPROM, the operation is completed before return
;* IX and A preserved, returns Z=1 (.EQ.) if OK
;*
;* Note: Byte writing to the FLASH and EEPROM arrays is a violation
;* of the HC9S12 specification. Doing so, will reduce long term
;* data retention and available prog / erase cycles
;*
;*********************************************************************
WriteA2IX: pshx ;preserve original address
pshd ;preserve original data
bsr CheckModule
bmi ExitWrite ;deny access (monitor or pseudo vector)
beq isWRAMbyte
cmpa 0,x ;FLASH or EEPROM needs programming
beq ExitWrite ;exit (OK) if already the right data
ldab 0,x ;$FF if it was erased
incb ;Z=1 if location was erased first
bne ExitWrite ;exit w/ Z=0 to indicate error
tfr x,b ;test least significant bit
bitb #1 ;is B0 = 1?
bne isOddAdr ;then it's odd addr.
isEvenAdr: ldab 1,x ;low byte of D (A:B) from memory
bra DoProgram
isOddAdr: tab ;move to low byte of D (A:B)
dex ;point to even byte
ldaa ,x ;high byte of D (A:B) from memory
bra DoProgram
isWRAMbyte: staa 0,x ;write to RAM or register
clra ;force Z=1 to indicate OK
bra ExitWrite
; Programs D to IX in either FLASH or EEPROM
DoProgram: bsr abClr ;abort commands and clear errors
cpx #RomStart ;simple test only
blo itsEE ; details already verified
bsr ProgFlash ;program the requested location
bra ExitWrite ;exit (Z indicates good or bad)
itsEE: bsr ProgEE ;program the requested location
; exit Write?2IX functions (Z indicates good or bad)
ExitWrite: puld ;restore original data (D)
pulx ;restore original address (IX)
rts
;*********************************************************************
;* Progee - program a single word in the HCS9S12 EEPROM
;* the location is assumed to be previously erased. This routine
;* waits for the command to complete.
;*
;* On entry... IX - points at the EEPROM address to be programmed
;* A - holds the data value to be programmed
;*
;* Calling convention:
;* bsr Prog1ee
;*
;* Returns: IX unchanged and A = ESTAT shifted left by 2 bits
;* Z=1 if OK, Z=0 if protect violation or access error
;*********************************************************************
ProgEE: std ,x ;latch address & data to program
ldaa #ProgWord ;Select program word command
staa ECMD ;issue word program command
ldaa #CBEIF
staa ESTAT ;[pwpp] register command
nop ;[p]
nop
nop
ChkDoneEE: ldaa ESTAT ;[prpp] (min 4~ before 1st read)
anda #$C0 ; mask all but 2 msb
lsla ;CCIF now in MSB
bpl ChkDoneEE ;wait for queued commands to finish
asla ;A=00 & Z=1 unless PVIOL or ACCERR
xProgEE rts
;
; utility sub to abort previous commands in flash and EEPROM
; and clear any pending errors
;
abClr: psha
ldaa #PVIOL+ACCERR ;mask
staa ESTAT ;abort any command and clear errors
staa FSTAT ;abort any command and clear errors
pula
rts
;*********************************************************************
;* Progflash - programs one byte of HCS9S12 FLASH
;* This routine waits for the command to complete before returning.
;* assumes location was blank. This routine can be run from FLASH
;*
;* On entry... IX - points at the FLASH byte to be programmed
;* A holds the data for the location to be programmed
;*
;* Calling convention:
;* bsr Prog1flash
;*
;* Uses: DoOnStack which uses SpSub
;* Returns: IX unchanged and A = FSTAT bits PVIOL and ACCERR only
;* Z=1 if OK, Z=0 if protect violation or access error
;*********************************************************************
ProgFlash: pshd
cpx #$8000 ; if <$8000 then bank 3E
blo its3E ;set ppage to 3E
cpx #$C000 ; if > $BFFF then bank 3F
blo ProgFlash1 ;set ppage 3F
movb #$3F,PPAGE ;
bra ProgFlash1
its3E: movb #$3E,PPAGE ;
ProgFlash1: ldab PPAGE
lsrb ; calculate the value of the block select bits based
lsrb ; on bits 3:2 of the PPAGE register value. (<256k)
ldy #SectorSize ; get high byte of size
cpy #$0200 ; if larger than $200 shift again
beq nBlockLoopb
lsrb ; on bits 4:3 of the PPAGE register value. (512k)
nBlockLoopb: comb
andb #$03 ; mask off all but the lower 2 bits.
stab FCNFG ; select the block to program.
cmpb #$00 ; if block zero use DoOnStack method
puld
beq ProgFlashSP
ProgFlshRom: std ,x ;latch address & data to program
ldaa #ProgWord ;Select program word command
staa FCMD ;issue byte program command
ldaa #CBEIF
bsr SpSub ;register command & wait to finish
ldaa FSTAT
anda #$30 ;mask all but PVIOL or ACCERR
rts
ProgFlashSP: std ,x ;latch address and data
ldaa #ProgWord ;Select program word command
staa FCMD ;issue byte program command
;
; DoOnStack will register the command then wait for it to finish
; in this unusual case where DoOnStack is the next thing in program
; memory, we don't need to call it. The rts at the end of DoOnStack
; will return to the code that called Prog1flash.
;
;*********************************************************************
;* DoOnStack - copy SpSub onto stack and call it (see also SpSub)
;* De-allocates the stack space used by SpSub after returning from it.
;* Allows final steps in a flash prog/erase command to execute out
;* of RAM (on stack) while flash is out of the memory map
;* This routine can be used for flash word-program or erase commands
;*
;* Calling Convention:
;* bsr DoOnStack
;*
;* Uses 22 bytes on stack + 2 bytes if BSR/bsr used to call it
;* returns IX unchanged
;************
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -