⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 myextra.asm

📁 8051 monitor programm: - use external ram to run user program - use eeprom to save user program
💻 ASM
📖 第 1 页 / 共 4 页
字号:


ssreg:
	mov	dptr, #sfr2+1
	acall	pstr_h
        acall   pequal
        mov     a, sp
	add	a, #252
	mov	r0, a
        mov     a, @r0
        acall   phexsp		;print psw
        mov     dptr,#sfr3+1
        mov     r0, 0xA8
        acall   psfr		;print ie
        mov     dptr,#sfr4+1
        mov     r0, 0xB8
        acall   psfr		;print ip
        mov     dptr,#sfr5+1
        mov     r0, 0x89
        acall   psfr		;print tmod
        mov     dptr,#sfr6+1
        mov     r0, 0x88
        acall   psfr		;print tcon
        mov     dptr,#sfr7+1
        mov     r0, 0x98
        acall   psfr		;print smod
        mov     dptr,#sfr8+1
        mov     r0, 0x87
        acall   psfr		;print pcon
        mov     a, #'T'
        acall   cout_h
        mov     a, #'0'
        acall   cout_h
        acall   pequal
        mov     a, 8Ch
        acall   phex_h		;print Timer 0
        mov     a, 8Ah
        acall   phex_h
        acall   space_h
        mov     a, #'T'
        acall   cout_h
        mov     a, #'1'
        acall   cout_h
        acall   pequal
        mov     a, 8Dh		;print Timer 1
        acall   phex_h
        mov     a, 8Bh
        acall   phex_h
        acall   newline_h
        ajmp    step1

psfr:   acall   pstr_h
        acall   pequal
        mov     a, r0
        ajmp    phexsp



;skip the next instruction
ssskip:
	mov	r0, #23
ssskip2:acall	space_h
	djnz	r0, ssskip2
        mov     dptr,#sskip1
        acall   pstr_h
	mov	a, sp
	add	a, #249
	mov	r0, a		;set r0 to point to pc on stack
	mov	a, @r0
	mov	lastpc, r6	;keep r6/r7 safe in lastpc
	mov	r6, a		;put user's pc into r6/r7
	inc	r0
	mov	a, @r0
	mov	(lastpc+1), r7
	mov	r7, a
	mov	a, r2
	push	acc
	mov	a, r3
	push	acc
	mov	a, r4
	push	acc
        setb    psw.1           ;tell it to use a compact format
        acall   disasm		;run disasm to show 'em what was skipped
	pop	acc
	mov	r4, a
	pop	acc
	mov	r3, a
	pop	acc
	mov	r2, a
        mov     a, sp
        add     a, #249
        mov     r0, a           ;set r0 to point to pc on stack
	mov	a, r6
        mov     r6, lastpc	;restore r6/r7
	mov	lastpc, a	;update lastpc with next inst addr
	mov	@r0, a		;also update user's pc!!
	inc	r0
	mov	a, r7
	mov	r7, (lastpc+1)
	mov	(lastpc+1), a
	mov	@r0, a
	ajmp	step1

sschacc:
        mov     a, sp
	add	a, #251
	mov	r0, a		;r0 points to acc on stack
        mov     dptr, #chaccs1
        acall   pstr_h
        lcall   ghex
        jc      chacc2
	jb	psw.5, chacc2
        mov     @r0, a
        acall   newline_h
        ajmp    step1
chacc2: mov     dptr, #abort
        acall   pstr_h
        ajmp    step1




;stuff some of the disassembler tables, strings, etc since we have a
;bit of space before the beginning of the editor command code


       ;opcode offset table (gives #bytes for the instruction
       ;and the number of the routine to print the operands)

opot1:  .db     0xAD, 0x06, 0x6F, 0x39, 0x39, 0x46, 0x49, 0x49 ;0
        .db     0x63, 0x06, 0x6F, 0x39, 0x39, 0x46, 0x49, 0x49 ;1
        .db     0x63, 0x06, 0xAD, 0x39, 0x16, 0x0E, 0x11, 0x11 ;2
        .db     0x63, 0x06, 0xAD, 0x39, 0x16, 0x0E, 0x11, 0x11 ;3
        .db     0x66, 0x06, 0x1A, 0x1F, 0x16, 0x0E, 0x11, 0x11 ;4
        .db     0x66, 0x06, 0x1A, 0x1F, 0x16, 0x0E, 0x11, 0x11 ;5
        .db     0x66, 0x06, 0x1A, 0x1F, 0x16, 0x0E, 0x11, 0x11 ;6
        .db     0x66, 0x06, 0x22, 0x69, 0x16, 0x1F, 0x92, 0x92 ;7
        .db     0x66, 0x06, 0x22, 0xA1, 0x4D, 0x83, 0x86, 0x86 ;8
        .db     0x9B, 0x06, 0x96, 0x9D, 0x16, 0x0E, 0x11, 0x11 ;9
        .db     0x26, 0x06, 0x22, 0x5D, 0x4D, 0xAD, 0x8E, 0x8E ;A
        .db     0x26, 0x06, 0x42, 0x3D, 0x2F, 0x2B, 0x37, 0x37 ;B
        .db     0x46, 0x06, 0x42, 0x3D, 0x39, 0x0E, 0x11, 0x11 ;C
        .db     0x46, 0x06, 0x42, 0x3D, 0x39, 0x57, 0x11, 0x11 ;D
        .db     0xA5, 0x06, 0x11, 0x11, 0x39, 0x0E, 0x11, 0x11 ;E
        .db     0xA9, 0x06, 0x89, 0x89, 0x39, 0x1A, 0x89, 0x89 ;F

mnot1:  ;mnunonic offset table (gives offset into above table)

        .db     0x5A, 0x0E, 0x48, 0x73  ;nop, ajmp, ljmp, rr
        .db     0x2B, 0x2B, 0x2B, 0x2B  ;inc, inc, inc, inc
        .db     0x30, 0x00, 0x43, 0x75  ;jbc, acall, lcall rrc
        .db     0x21, 0x21, 0x21, 0x21  ;

        .db     0x2E, 0x0E, 0x67, 0x6E  ; etc...
        .db     0x06, 0x06, 0x06, 0x06  ;
        .db     0x38, 0x00, 0x6A, 0x70  ;
        .db     0x0A, 0x0A, 0x0A, 0x0A  ;

        .db     0x33, 0x0E, 0x5D, 0x5D  ;
        .db     0x5D, 0x5D, 0x5D, 0x5D  ;
        .db     0x3B, 0x00, 0x12, 0x12  ;
        .db     0x12, 0x12, 0x12, 0x12  ;

        .db     0x41, 0x0E, 0x8F, 0x8F  ;
        .db     0x8F, 0x8F, 0x8F, 0x8F  ;
        .db     0x3E, 0x00, 0x5D, 0x35  ;
        .db     0x4C, 0x4C, 0x4C, 0x4C  ;

        .db     0x7C, 0x0E, 0x12, 0x4F  ;
        .db     0x24, 0x4C, 0x4C, 0x4C  ;
        .db     0x4C, 0x00, 0x4C, 0x4F  ;
        .db     0x80, 0x80, 0x80, 0x80  ;

        .db     0x5D, 0x0E, 0x4C, 0x2B  ;
        .db     0x57, 0x92, 0x4C, 0x4C  ;
        .db     0x12, 0x00, 0x1C, 0x1C  ;
        .db     0x15, 0x15, 0x15, 0x15  ;

        .db     0x63, 0x0E, 0x19, 0x19  ;
        .db     0x84, 0x88, 0x88, 0x88  ;
        .db     0x60, 0x00, 0x78, 0x78  ;
        .db     0x1F, 0x27, 0x8B, 0x8B  ;

        .db     0x53, 0x0E, 0x53, 0x53  ;
        .db     0x19, 0x4C, 0x4C, 0x4C  ;
        .db     0x53, 0x00, 0x53, 0x53  ;
        .db     0x1C, 0x4C, 0x4C, 0x4C  ;


mnot2:  .db     0x2B, 0x21, 0x06, 0x0A  ;inc, dec, add, addc
        .db     0x5D, 0x12, 0x8F, 0x4C  ;orl, anl, xlr, mov
        .db     0x4C, 0x80, 0x4C, 0x15  ;mov, subb, mov, cjne
        .db     0x88, 0x27, 0x4C, 0x4C  ;xch, djnz, mov, mov

;---------------------------------------------------------;
;                                                         ;
;                  EEPROM Boot Loader                     ;
;    detect P3.5 if P3.5 == 0 then run EEPROM Booting     ;
;---------------------------------------------------------;

;register usage:
; R4,    Flags:
;         bit0: 0=display CODE memory, 1=display DATA memory
;         bit1: 0=editing disabled, 1=editing enabled
;         bit2: 0=editing in hex, 1=editing in ascii
;         bit3: 0=normal, 1=in middle of hex entry (value in r5)
; R6/R7, current memory location
;

.org    locat+0x800
.db     0xA5,0xE5,0xE0,0xA5     ;signiture
.db     253,255,0,0             ;id (253= startup)
.db     0,0,0,0                 ;prompt code vector
.dB     0,0,0,0                 ;reserved
.db     0,0,0,0                 ;reserved
.db     0,0,0,0                 ;reserved
.db     0,0,0,0                 ;user defined
.db     255,255,255,255         ;length and checksum (255=unused)
.db     "EEPROM booting",0

.org    locat+0x0840            ;executable code begins here

        JNB P3.5,boot
        ret

boot:   acall boot_eeprom


; change Fix_baud to 9600
;this little program is an example of how to use the "init" type
;of startup program to initialize the baud rate and the other
;related memory locations, so that PAULMON2 will *not* attempt
;to do automatic baud rate detection, even if it configured to
;do automatic baud rate detection by default.  For boards with
;flash rom, this allows the board to used for a dedicated purpose
;without having to do automatic baud rate detection every time
;the power is cycled.  Startup programs other than hardware
;initialization should usually used type 253 instead of 249.

;.equ    baud_const, 255         ;57600 baud w/ 11.0592 MHz
;.equ   baud_const, 253         ;19200 baud w/ 11.0592 MHz
;.equ   baud_const, 252         ;19200 baud w/ 14.7456 MHz
;.equ   baud_const, 243         ;4808 baud w/ 12 MHz
;.equ    baud_const, 250         ; 9600 baud w/11.0592 MHz
.equ    baud_const, 244         ; 9600 baud w/22.1184 MHz

.org    locat+0x900             ; i.e., 1900h

.db	0xA5,0xE5,0xE0,0xA5	;signiture bytes
.db	249,255,0,0		;id (35=prog, 249=init, 253=startup, 254=cmd)
.db	0,0,0,0			;prompt code vector
.db	0,0,0,0			;reserved
.db	0,0,0,0			;reserved
.db	0,0,0,0			;reserved
.db	0,0,0,0			;user defined
.db	255,255,255,255		;length and checksum (255=unused)
.db	"Fixed Baud Rate",0
.org    locat+0x940             ;executable code begins here

	mov	a, #baud_const
	mov     0x7B, a
        mov     0x7A, a         ;store the baud rate for next warm boot.
        mov     0x79, a
        mov     0x78, a
        xrl     0x7A, #01010101b
        xrl     0x79, #11001100b
        xrl     0x78, #00011101b
	ret

;------------------------- my code ------------------------------
; back to monitor program path with printout accumulator and
; psw's content
; W.Sirichote 25 July 1999

monitor:
        push psw
        push acc

        lcall newline
        mov  dptr, #accumulator
        lcall pstr
        pop  acc
        lcall phex

        lcall newline
        mov dptr, #PSW_REG
        lcall pstr
        pop psw
        mov a,psw
        lcall phex
        lcall newline

        ljmp  0         ; go to reset condition

accumulator: .db "Accumulator = ",0
PSW_REG:     .db "PSW = ",0

;----------------------------------------------------------
; getnum() and _atoi()
; W.Sirichote 16 August 1999

; 16 bit multiply of AB by R3-4, result in AB
;

mul16:    MOV     R6,A           ; Save LO1
        MOV     A,R3           ; Get LO2
        MUL     AB             ;   Multiply HI1 * LO2
        MOV     R5,A           ; Save partial product
        MOV     B,R6           ; Get LO1
        MOV     A,R4           ; Get HI2
        MUL     AB             ;   Multiply LO1 * HI2
        MOV     R4,A           ; Save partial product
        MOV     A,R3           ; Get LO2
        MOV     B,R6           ; Get LO1
        MUL     AB             ;   Multiply LO2 * LO1
        XCH     A,B            ; Save low & get high
        ADD     A,R4           ; Add in carry from LO1 * HI2
        ADD     A,R5           ; Add in carry from HI1 * LO2
        XCH     A,B            ; Restore proper order
	RET

; Convert ASCII string to number: int _atoi(string)
; r1 string pointer

_atoi:  
        CLR     A              ; Get ZERO
        MOV     R3,A           ; Set LOW
        MOV     R4,A           ; Set HIGH
        MOV     R7,A           ; Assume positive
A1:     MOV     A,@R1          ; Get char
        INC     R1             ; Advance
        CJNE    A,#'-',A3      ; Not minus
        INC     R7             ; Set negative flag
A2:      MOV     A,@R1          ; Get char
        INC     R1             ; Advance
A3:      CLR     C              ; Insure no carry
        SUBB    A,#'0'         ; Convert to binary
        CJNE    A,#10,*+3      ; Non-destructive compare
        JNC     A4             ; End of number
        MOV     R2,A           ; Save for later
        MOV     A,#10          ; *10
        MOV     B,#0           ; Zero high
        LCALL   mul16           ; Multiply result
        ADD     A,R2           ; Include digit
        MOV     R3,A           ; Save LOW
        MOV     A,B            ; Swap
        ADDC    A,#0           ; Insure high incs
        MOV     R4,A           ; Save high
        SJMP    A2             ; And go again
A4:      MOV     A,R3           ; Get LOW result
        MOV     B,R4           ; Get HIGH result
        DJNZ    R7,A5          ; Negative sign?
      ;  LJMP    neg           ; Yes, convert
A5:      RET

;=======================================================
; int getnum() return integer in BA
; get decimal string then convert to int
; use 6-byte RAM at f0h-f5h, eg. '65535' 0

_getnum: mov  r1,#0xf0
_getnum2:
         lcall cin
         cjne a,#0dh,check_BS
         mov  @r1,#0            ; put terminator
         mov  r1,#0xf0
         lcall _atoi
         ret                    ; return BA as an integer

check_BS: cjne a,#8,check_FF
          lcall cout
          dec  r1
          sjmp  _getnum2

check_FF: cjne a,#0x0c,save_char
          lcall cout
          inc r1
          sjmp _getnum2

save_char: lcall cout
           mov @r1,a
           inc r1
           sjmp _getnum2


;==========================================================
;   ZAP eeprom service routines
;
;    W.Sirichote Feb 5, 2002
;==========================================================

.org    locat+0xA00             ; i.e. 0x1A00
.db     0xA5,0xE5,0xE0,0xA5     ;signiture
.db     254,'Z',0,0             ;id (254=user installed command)
.db     0,0,0,0                 ;prompt code vector
.dB     0,0,0,0                 ;reserved
.db     0,0,0,0                 ;reserved
.db     0,0,0,0                 ;reserved
.db     0,0,0,0                 ;user defined
.db     255,255,255,255         ;length and checksum (255=unused)
.db     "ZAP EEPROM",0

.org    locat+0x0A40            ;executable code begins here

loop_eeprom:  mov  dptr,#eeprom_menu
       lcall pstr
       mov  a,#'>'
       lcall cout
       lcall cin
       cjne a,#'1',next2
       acall save_pgm
       sjmp loop_eeprom

next2: cjne a,#'2',next3
       acall eeprom_dump
       sjmp loop_eeprom

next3: cjne a,#'3',next4
       acall boot_eeprom
       sjmp loop_eeprom

next4: mov  r6,#0x00
       mov  r7,#0x80    ; return to start address of SRAM 0x8000 
       ljmp  newline_h

eeprom_menu: .db 13,10,"24LC256 EEPROM functions 1 SAVE, 2 DUMP, 3 LOAD",13,10,0


;==================== eeprom drivers =========================
; Generate a START condition & TX char in A

ICstrt: SETB   P3.4            ;SDA = 1
        SETB    P1.0            ;SCL = 1
	NOP
        NOP
        CLR     P3.4            ;SDA = 0 - START
	NOP
        NOP
        CLR     P1.0            ;SCL = 0 - Ready for first bit
        RET

; Send 8 bit character in A

ICsend: MOV     R7,#8          ;8 bits ber byte
send1:  RLC     A               ; Get next bit to send
        MOV     P3.4,C          ;Write bit to data line

;        MOV     P1.7,C          ; use P1.7 as a I2C functioning

        SETB    P1.0            ;Toggle CLOCK high
        NOP
        NOP
        NOP
        NOP
        CLR     P1.0            ;Toggle CLOCK low
        DJNZ    R7,send1           ;Send all bits

        SETB    P3.4            ;Release DATA line
        SETB    P1.0            ;9'th clock
	NOP
        NOP
        NOP
        NOP

        MOV     C,P3.4          ;Get ACK bit
        CLR     P1.0            ;Return clock LOW
	RET
;
; Read 8 bits of data into ACC
;

ICread: MOV     R7,#8          

read_bit: SETB    P1.0
	NOP
        NOP
        NOP
        NOP

        MOV     C,P3.4

;        MOV     P1.7,C  ; also for reading I2C indicator

        RLC     A               

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -