8051 programming

Al Lipper alipper at cardozo.org
Sat Mar 20 20:32:00 GMT 1999


--=====================_4473098==_
Content-Type: text/plain; charset="us-ascii"

Ord,
Thanks so much for your interest!  I don't think we need too uch assembly
programming, but some.  Basicially, we've changed over from an Intel
80C51GB (that is no longer made) to a Phillips 80C552.  They have similar
features, but the capture/compare timers  and A/D converter have different
register structures, so the old software needs to be modified to work with
the philips chip.  The other thing we need done is to revise our old flash
memory loader to work with a new 5v flash (we used to use a 12v version).
All the current code is well commented.  I've attached the files that
contain it, so perhaps you can look over them and tell me what you think.  

			Al

At 02:23 PM 3/20/99 -0500, you wrote:
>Al,
>
>I do a lot of 8051 programming, mostly in assembler (with a little MCS basic
>for fun now and then).
>
>Perhaps I can help you with the ECU6 software.  I can not spend too much
>time with it, but if you have some specific problems to solve, or algorithms
>that you need let me know.
>
>Ord
>
>

--=====================_4473098==_
Content-Type: text/plain; charset="us-ascii"
Content-Disposition: attachment; filename="Fload.asm"

;********************************************************************
;  8051 Boot Loader ver 3.0
;  Download standard Intel hex format files
;  Assemble using ASM51.EXE by MetaLink Corp.
;  Author: Steven J. Merrifield, sjm at ee.latrobe.edu.au
;  sjm 11 Apr 95 Mike Sullivan
;  
;  Al Lipper 7/26/97 Implemented for ECU6
;********************************************************************

; Using the 87C51GB.
$MOD51GB

r0b0			equ	00h		; Register R0, Bank0
r1b0			equ	01h		; Register R1, Bank0
r2b0			equ	02h		; Register R2, Bank0
r3b0			equ	03h		; Register R3, Bank0
r4b0			equ	04h		; Register R4, Bank0

cret              equ 0dh             ; carriage return
lf                equ 0ah             ; linefeed

BaudLoad	equ	-39		;9600 at 12MHz
SMOD		equ	00000001b	; Bit to set in PCON for double baud rate


;********************************************************************
; Interrupt vector table
;********************************************************************
            org 0000h               ; System reset      RST
               	ljmp main
            org 000bh               ; Timer 0           TF0
            	ljmp wdt_isr      ;WDT ISR to keep CPU going

;********************************************************************
; Main program starts here
;********************************************************************
            org 0030h
main:           
                lcall wdt_init      ; init timer 0 for WDT reset
                lcall s_init          ; init serial port
                lcall intro         ; print welcome message
                lcall e_prompt      ; erase prompt
                LCALL F_ERASE       ; call flash erase routine
		    lcall hexload		; read hex file and save in flash
done_main:	    lcall end_msg		; Display done message
		    sjmp done_main	; loop forever		

; Read Intel hex file from serial port and store in flash
HEXLOAD:
        PUSH    PSW
                mov dptr,#p_rxhex	; Print 'Ready for hex file' message
                lcall outstr
ANL     PCON,#11110000B ; Clear flag bits

        SJMP    GetHex		; Wait for either ':' (Start),
                                ;  CR, or LF.
Ck_CR:  CJNE    A,#CRET,Ck_LF     ;  Any other chars will set the
        SJMP    WAIT            ;  error flag.

Ck_LF:  CJNE    A,#LF,Ck_C
        SJMP    WAIT

Ck_C:	CJNE    A,#3,CharErr	; Check for <Ctrl-C>
        SJMP    HEX_DONE

CharErr:ORL     PCON,#8         ; Set error flag
	CALL	C_OUT
        SJMP    WAIT

GetHex: JNB     TI,$
        CLR     TI
        MOV     SBUF,#'>'       ; Output pace character

WAIT:   CALL    GetChar         ; Wait to receive a character

        CJNE    A,#':',Ck_CR    ; Wait for start character ?
	CALL	C_OUT

        SETB    F0              ; --------- THE MAIN ENTRY POINT FOR HEXLOAD --------
        MOV     R2,#0           ; Start checksum
        CALL    RdByte          ; 1) Get record length
        MOV     R0,A            ; Save length

        CALL    RdByte          ; 2) Get high address
        MOV     DPH,A

        CALL    RdByte          ; 3) Get low address
        MOV     DPL,A

        CALL    RdByte          ; 4) Get record type
        JZ      GetDat          ; 0 if data, 1 if last record
        CLR     F0              ; Clear flag

GetDat: MOV     A,R0            ; Check record length
        JZ      IsEnd

DataIn: CALL    RdByte          ; 5) Get a byte
        JNB     F0,NoStor       ; Store if data record

WriteX: 
;	movx	@dptr, a
	  LCALL	WR_BYTE	  ; Write to flash
	  CJNE	A, #02h, NoHexErr	; Check for pgm error
	  MOV		R4, #02h		; Save code for program error
;	  SJMP	HEX_DONE		; Abort loading & report error		
NoHexErr:
	  INC		DPTR		  ; Point to next addr. in flash
	  
NoStor: DJNZ    R0,DataIn       ; Get more bytes
        DEC     R0              ; R0 = FF

IsEnd:  CALL    RdByte          ; Get checksum byte
        MOV     A,R2
        JZ      ChkOK
        ORL     PCON,#4
        
ChkOK:  MOV     A,#CRET
        CALL    C_OUT

        MOV     A,R0            ; Will be FF for data record
        JNZ     GetHex          ; Read another record?
                                
        MOV     A,#0CH          ; Now check for any errors
        ANL     A,PCON
        JZ      HEX_DONE

; Checksum Error        
cs_error:
	  mov 	dptr,#p_cserror
        lcall	outstr
	  mov		R4, #04		; Save code for Checksum error

HEX_DONE:
        POP     PSW
        RET                     ; All done so return

GetChar:JNB     RI,$            ; Character in SBUF ?
        MOV     A,SBUF
        CLR     RI
        CLR     ACC.7           ; Clear parity bit
	RET

; Get 2 chars & make a 2 digit byte.  Return byte in acc.
RdByte: SETB    PSW.1           

DoAgin: MOV     R3,A
        CALL    GetChar         ; Get a single character
        CALL    C_OUT           ; Echo it

        CLR     C
        SUBB    A,#'0'
        JNC     Do_1            ; Not a digit ?  (<30H ?)

        ORL     PCON,#8         ; Set error flag
        CLR     F0              ; DO NOT store this record

Do_1:   SUBB    A,#10           ; Test for A-F
        JC      IsNmbr
        SUBB    A,#7            ; Adjust for gap

IsNmbr: ADD     A,#10           ; Restore
        ANL     A,#0FH
        JBC     PSW.1,DoAgin    ; 2nd time ?

        SWAP    A
        ORL     A,R3
        SWAP    A               ; 2 digits in ACC

        XCH     A,R2            ; Get Checksum
        ADD     A,R2            ; Update it and
        XCH     A,R2            ;  get byte back.
        RET

C_OUT2: CALL    C_OUT           ; Send the character twice.

C_OUT:  JNB     TI,$            ; Wait til last character gone.
        CLR     TI              ; Clear interrupt flag.
        MOV     SBUF,A          ; Write out character.

        CJNE    A,#CRET,CONT      ; If it was <CR> then follow with <LF>.
        JNB     TI,$
        CLR     TI
        MOV     SBUF,#LF        ; Output linefeed.

CONT:   RET


;********************************************************************
;  Erase prompt message
;********************************************************************
e_prompt:       mov dptr,#p_ersprmpt   ; print erase prompt
                lcall outstr        
                lcall inchar         ; get char from serial port
                cjne a,#'e',e_prompt ; if "e" not pressed, loop
                lcall inchar                
                cjne a,#'r',e_prompt ; if "r" not pressed, loop
                lcall inchar                
                cjne a,#'a',e_prompt ; if "a" not pressed, loop
                lcall inchar                
                cjne a,#'s',e_prompt ; if "s" not pressed, loop
                lcall inchar                
                cjne a,#'e',e_prompt ; if "e" not pressed, loop
                ret

;********************************************************************
; Print welcome message
;********************************************************************
intro:          mov dptr,#p_intro1
                lcall outstr
                mov dptr,#p_intro2
                lcall outstr
                ret
;********************************************************************
; Print finished message or error
;********************************************************************
; NOTE: If more than one error occurs, only the first one will be reported
end_msg:        
		mov A, R4				; Get Error code
		cjne	A, #00h, erase_err	; Check for No Error

No_Err:	mov dptr,#p_finish
		lcall outstr
		sjmp	end_exit
	
erase_err:	cjne	A, #01h, pgm_err	; Check for Erase Error
		mov dptr,#p_ererror
		lcall outstr
		sjmp	end_exit

pgm_err:	cjne	A, #02h, zero_err; Check for Zeroing Error
		mov dptr,#p_pgmerror
		lcall outstr
		sjmp	end_exit

zero_err:	cjne	A, #03h, cksm_err; Check for Checksum Error
		mov dptr,#p_zrerror
		lcall outstr
		sjmp	end_exit

cksm_err:	cjne	A, #04h, inval_err; Check for undefined Error code
		mov dptr,#p_cserror
		lcall outstr
		sjmp	end_exit

inval_err:	mov dptr,#p_iverror
		lcall outstr
end_exit:	
		ret

;********************************************************************
; Wait until a char is received from the serial port, and return
; that char in the accumulator.
;********************************************************************
inchar:         jnb ri,inchar       ; wait until ri is set
                clr ri              ; clear interrupt
                mov a,sbuf          ; get character
                ret

;********************************************************************
; Wait until tx ready, then send a char out serial port
;********************************************************************
outchar:        jnb ti,outchar      ; wait until ti is set
                clr ti              ; clear it
                mov sbuf,a          ; send acc to serial buffer
                ret

;********************************************************************
; Send a null terminated string out serial port
;********************************************************************
outstr:
	clr a
                movc a, at a+dptr      ; get character
                jz exit             ; stop if char == null
                lcall outchar       ; else send it
                inc dptr            ; point to next char
                sjmp outstr
exit:           
	ret

;********************************************************************
; Init serial port
;********************************************************************
; *** Alternate baud rate init routine for 9600 baud at 12 Mhz (Using Timer2) ***
; Taken from Intel serio2m.asm.
;
S_INIT:
	CLR	TR1
	MOV	SCON,#01011010B	;TI set indicates transmitter ready.
				; mode 1,REN
	MOV	T2CON,#00110000B; Initialize Timer 2 as Baud Rate generator
	orl	PCON,#SMOD	; Set to double rate.
	setb	smod
	mov	rcap2h,#High BaudLoad	; Set reload value
	mov	rcap2l,#low Baudload
	setb	tr2		; start timer.
	ret
;

ck_error:       
                mov dptr,#p_cserror
                lcall outstr

stop:           sjmp stop

p_intro1:        db cret,'ECU Flash Memory Loader v1.1 7/24/97',cret,lf,0
p_intro2:        db cret,'(c) 1997 Injection Logic',cret,lf,0
p_ersprmpt:        db cret,lf,'Enter <erase> to Erase Chip',cret,lf,0
p_finish:        db cret,'Finished downloading: Switch Back to Run Mode',cret,lf,0
p_zero:        db 'Zeroing...',0
p_erase:        db 'Erasing...',0
p_erdone:       db 'Erase Completed',cret,lf,0
p_rxhex:       db cret,lf,'Ready to receive Intel Hex file',cret,lf,0

; Error message text.  Note R4 will contain error code (or 0 for no error)
p_ererror:        db cret,lf,'Flash Erase Error',0		; R4 = 1
p_pgmerror:        db cret,'Flash Programming Error during HEXLOAD',cret,lf,0	; R4 = 2	
p_zrerror:        db cret,lf,'Erase Zeroing Error',0	; R4 = 3
p_cserror:        db cret,'Serial Data Checksum Error Detected ',cret,lf,0	; R4 = 4
p_iverror:        db cret,'Invalid Error Code Returned ',cret,lf,0	; R4 > 4





;
;------------------------------------------------------------------------------
; Macros
;
;   The following macros are used to control assembly options.
;------------------------------------------------------------------------------

WAIT6us              MACRO                     ; wait 6 microseconds @ 12MHz
                push acc
        mov     acc,#01
                djnz    acc,$
                pop acc
      ENDM

;
; The 10us time delay
;

WAIT10us             MACRO                    ; wait 10 microseconds @ 12MHz
                push acc
                mov     acc,#03h
                djnz    acc,$
                pop acc
                      ENDM
;
; 10 ms time delay
;

WAIT10ms             MACRO                   ; wait 10 millisecond @ 12MHz
                push acc
                mov acc, #10
W10:   push acc
        mov     acc,#249
                djnz    acc,$
                mov     acc,#249
                djnz    acc,$
                pop acc
                djnz acc, W10
                pop acc
                    ENDM
;-----------------------------------------------------------------------------
;
; Critical Design Information:
;
;   1. For Flash devices, program/erase timing is extremely important. This
;      software uses a busy-wait loop to time the program and erase functions.
;      Processor/memory speed is therefore of critical importance to correct
;      and reliable programming and erasure. In general, use of this software
;      requires tailoring it to the timing of each individual system.
;   2. Programming Flash devices requires a 12.0V power supply.
;	   Control of Vpp is system dependent. Users must supply one function
;	   -- VPP -- that will be called to turn Vpp on or off.  On entry to VPP,
;	   the ACC register contains a code specifying the desired operation as
;	   follows:
;
;		ACC = 0 	Turn Vpp off
;		ACC = 1		Turn Vpp on
;      
;
;
; Abstract:
;
;   This software is designed to support the In-system programming requirements
;   of Intel's Flash memory.
;
;   This software module is supplied in source code form. The software is
;   written in MSC-51 assembly language using Intel ASM51 assembler. It
;   is designed to be assembled and linked with other system and application
;   software to form an integrated program. 
;
;   The following functions are supported:
;
;     1. Erase. Used to erase a single Flash memory before programming.
;     2. Program byte. Used to program single data elements, typically for 
;	 data collection applications.
;
; Function Details:
;
;   Overview:
;
;   Erase
;     This operation erases the Flash memory whose base address is
;     contained in the DPTR register.  The the base address of the 28F010
;     Flash memory is mapped at 0000h.
;
;   Write Byte
;     This operation writes a single byte (in ACC) into the Flash memory
;     at the address contained in the DPTR register:
;
;           ACC         Byte data
;           DPTR        Flash memory address
;
; Hardware Configurations:
;
;   This software is designed and implemented for the MCS-51 family.
;
; Language
;
;   This software is designed to assemble under the Intel ASM51 Assembler,
;   on the IBM PC and compatibles.
;==============================================================================
;------------------------------------------------------------------------------
; Miscellaneous Definitions
;------------------------------------------------------------------------------
M_ETRIES_LOW    equ 0E8H       	; 1000 erase tries maximum low byte
M_ETRIES_HIGH   equ 03H        	; 1000 erase tries maximum high byte
M_PTRIES        equ 25        	; 25 program tries maximum
F_BASE_ADDRESS	equ 0000H	; Flash base address
F_ENDL		equ 00H		; flash last address+1 (LSB) - FFFFH is last addr.
F_ENDH		equ 00H		; flash last address+1 (MSB)

;------------------------------------------------------------------------------
; Command Definitions
;
;   These commands are written to the Flash memory to run the internal state
;   machine.
;------------------------------------------------------------------------------

C_ERAS          equ     020H                    ; enter erase state
C_PROG          equ     040H                    ; enter program state
C_EVER          equ     0A0H                    ; enter erase verify state
C_PVER          equ     0C0H                    ; enter program verify state
C_READ          equ     000H                    ; enter read state



;------------------------------------------------------------------------------
; Error Definitions
;
;   These error values are used to identify MBM operation errors.
;------------------------------------------------------------------------------

OK              equ     0                       ; no error
E_ERASE         equ     1                       ; erase operation failed
E_PROGRAM       equ     2                       ; program operation failed



;--------------------------------------------------------------------------
; This routine is used to erase the content of a 28F010.
; 
;		Input parameters :
;			DPTR	  = base address of the 28F010
;		Oputput parameters :
;
;		Other registers used 
;			R2,R3	=	number of erase pulses (high byte in R3)
;			R4	=	Code indicating error 
;------------------------------------------------------------------------------


f_erase:	
            mov dptr,#p_zero		; print 'Zeroing...'
            lcall outstr
		push	dph			; save dptr
		push	dpl
		mov	r4, #00h		; Reset error code (0 = no error)
;
; Erase algorithm suggests testing to see if flash is erased before erasing it.  This
; step is skipped since flash should not ordinarily be previously erased at this point.

; First set all bytes to 00H in preparation for erase.
wr_next_page:
		mov	dptr,#f_base_address	; load the flash base address 
wr_next:
		mov	a,#00h
		call 	wr_byte				; programm 00h 
		cjne	a,#e_program,nexta

		mov	R4, #03h		; Save zeroing error code
		sjmp	erase_end		; return Zeroing error

nexta:
		inc	dptr			; next address
	;Check to see if current address has reached last flash address
		mov	a,dpl			; first check low byte
		cjne	a, #f_endl, wr_next
		mov	a,dph			; then check hi byte
		cjne	a, #f_endh, wr_next
;
;

;-------------- now erase the 28F010

erase:  
		mov dptr,#p_erase	; print 'Erasing...'
            lcall outstr
		mov	dptr, #f_base_address
		mov  	r2, #M_ETRIES_LOW	; max. erase retries low byte
		mov  	r3, #M_ETRIES_HIGH	; max. erase retries high byte
						; max. erase retries = 1000
 
era_again: 
		mov  	a, #c_eras 
		movx 	@dptr, a		; write E_code to CMD register 
		movx 	@dptr, a		; write again to confirm 
		wait10ms
		mov  	a, #c_ever 
		movx 	@dptr, a 		; stop, enter erase verify 
		wait6us       			; for high voltage switch 

; Verify that flash is erased (all bytes contain FFh)
loop:
		clr 	a
		movx 	a, @dptr		; read back 
		cjne 	a, #0ffh, next_pulse 
		inc  	dptr   			; next address 
	;Check to see if current address has reached last flash address
		mov	a,dpl			; first check low byte
		cjne	a, #f_endl, loop
		mov	a,dph			; then check hi byte
		cjne	a, #f_endh, loop

;erased:
		mov	a, #ok			; return code
		sjmp	erase_end

	; Erase attempt failed, try erase again if less than 1000 attempts
next_pulse:
		dec	r2				; increment erase count
		cjne r2, #0ffh, era_again	; if less than 1000 continue
		dec r3
		cjne r3, #0ffh, era_again
		mov	a, #e_erase			; more than 1000, return error code

erase_end:
		push	acc				; save return code
		mov	dptr,#f_base_address	; address to flash
		mov	a,#c_read		; write read code
		movx	@dptr,a
		pop	 acc			; restore return code
		pop	dpl
		pop dph

            cjne a, #e_erase, ck_pgmerr	; check for erase error
		mov dptr,#p_ererror	; print 'Erase Error'
            lcall outstr
		mov	r4, #01h		; Save erase error code
		sjmp	er_exit
		
; at this point, a programming error is due to flash not zeroing correctly
ck_pgmerr:      
            cjne a, #e_program, er_success	; check for zeroing error 
		mov dptr,#p_zrerror	; print 'Zeroing Error'
            lcall outstr
		mov	r0, #03h		; Save zeroing error code
		sjmp	er_exit

er_success:	
		mov dptr,#p_erdone	; print 'Erase Completed'
            lcall outstr
er_exit:		
		ret
 
;*************************************************************************
;
;  NAME:	WR_BYTE
;
;  ABSTRACT:	This routine program a byte of data of a Flash memory 
;	using Quick Pulse programming algorithm.  The address is loaded in
;	DPTR register and the data is loaded in the accummulator.
;
;  INPUTS:	DPTR	programmed address
;		A	data
;
;  OUTPUTS:	none
;
;  REGISTERS MODIFIED:
;		R0	save data
;		R1	number of programming loops
;
;  ERROR:	A = 00h	programmed without error
;			A = 02h	failed to program
;
;  SUBROUTINES ACCESS DIRECTLY:
;		wait10us	delay 10us	(macro)
;		wait6us		delay 6us	(macro)
;  
;*************************************************************************


wr_byte:	
		
		push	r0b0			; save r0
		push	r1b0			; save r1

		mov	r0,a			; save data in acc.
		mov	r1, #m_ptries		; allow 25 prog pulses
again:	
		mov	a,#c_prog		; load code to program
		movx	@dptr, a		; write prog code to CMD reg.
		mov	a,r0			; restore data
		movx	@dptr, a		; write data

		wait10us			; programming pulse width

		mov	a,#c_pver		; load program verify code
		movx	@dptr, a		; stop prog., enter verify mode
						; switch to program verify mode
		wait6us			; wait for 6us 
		clr a				; ACC=0 for next instruction
		movx	a, at dptr			; read back 
		clr	c
		subb	a, r0			; compare with programmed data 
		jz	wr_done			; next address
		djnz	r1,again		; after 25 loops
		mov	a,#e_program		; return with error code
		sjmp 	err_done
wr_done:	
		mov	a,#ok			; return ok code
err_done:
		push	acc			; store return code
		mov	a,#c_read		; write read code
		movx	@dptr,a
		pop 	acc			; restore return code
		
		pop	r1b0			; restore r1
		pop	r0b0			; restore r0
		ret

;WDT routines - see Intel appnotes (AB-44)
;Initialize timer 0 for watchdog ISR
wdt_init:
                setb ea
                setb et0

                mov tmod, #01h
                mov tl0, #7fh
                mov th0, #0c0h

                setb tr0
                ret

; WDT reset - WDT needs to be reset every 16ms or it will reset the CPU
; Timer 0 is used to call this ISR to do this reset.
wdt_isr:
      ; setb p1.5        ;debug
                clr     tr0

                mov     wdtrst, #1eh
                mov     wdtrst, #0e1h

                mov     tl0, #7fh
                mov     th0, #0c1h
                setb tr0
       ; clr p1.5       ;debug
		CPL 	P1.6	; Invert Reset IC's (MAX805L) Watchdog timer bit
                reti


end


--=====================_4473098==_
Content-Type: text/plain; charset="us-ascii"
Content-Disposition: attachment; filename="EFI02.asm"

$NOPAGING
; 6/7/97 - added WDT routines
; efi00.asm     950204RHAL

;       ASM routines for Electronic Fuel Injection System.
;       Includes ISRs for RPM and injector pulsing.


; Using the 87C51GB.
$MOD51GB


;*************************************************************************

; Memory useage, Variable declaration, and Vector tables--

r0b0       equ    00h           ; Register R0, Bank0
r1b0       equ    01h           ; Register R1, Bank0

; Variables for use in/with ASM routines.

;       Note: Internal bits 00-0F use internal memory locations 20 and 21.
;       Internal Bits 00-07 for ASM only flags.

;       Internal Bits 08-0F for BASIC/ASM flags.
SP_SYNC    BIT    008h                  ; Set when Injector Pulse is to be
					;   Synchronized with Spark Pulse.
					;   Written by Main loop.  EX_ASYNC
					;   must be called by main loop when
					;   this value is changed.

;       Direct addresses 18H-21H of Internal RAM for BASIC/ASM variables.
;       These addresses are not used by the compiler
; External addresses FFF0-FFFF are used to transfer data to BASIC
OLD_CCAP0  DATA   018h                  ; Previous PCA0 capture value, 2
					;   bytes (lo-hi).  Used to compute
					;   Spark Pulse period.  Used only
					;   in ISR (Static Local).

PW1        DATA   01Ah                  ; Injector Pulse Width (count for
					;   PCA1), 2 bytes (lo-hi).  Data is
					;   passed from Main to ISR here.
					;   Main loop should clear EC0 when
					;   when writing these bytes.
RPMPW      DATA   01Ch                  ; Spark Pulse period, 2 bytes.  Data
					;   is passed from ISR to Main here.
					;   Main loop should clear EC0 when
					;   when reading these bytes.
APP        DATA   01Eh                  ; Async Injector Pulse Period.  Data
					;   is passed form Main to ISR here.
					;   Main loop should clear EC0 when
					;   when writing these bytes.
TICK15     XDATA   0FFF6H               ; Two byte counter, incremented
					;   every 15ms by WDT_ISR: for use by
					;   BASIC program in timed operations.

; A/D Converter addresses
ADC_0        DATA   084h                  ; A/D Converter channel 0
ADC_1        DATA   094h                  ; A/D Converter channel 1
ADC_2        DATA   0A4h                  ; A/D Converter channel 2
ADC_3        DATA   0B4h                  ; A/D Converter channel 3
ADC_4        DATA   0C4h                  ; A/D Converter channel 4
ADC_5        DATA   0D4h                  ; A/D Converter channel 5
ADC_6        DATA   0E4h                  ; A/D Converter channel 6
ADC_7        DATA   0F4h                  ; A/D Converter channel 7
ACON       DATA   097h                  ; A/D Converter control register
;A/D Converter uses FFF8-FFFF as mirror locations for the above registers
ADC_MIRR   XDATA  0FFF8h                ; A/D Mirror for transfer to BASIC

; Enter values into Interrupt Vector "Mirror."
	   ORG  0FE00H                  ; RESET VECTOR
	   JMP  WDT_INIT                ; INIT TIMER 0 FOR WDT RESET
	   ORG  0FE0Bh                  ; Timer 0           TF0
	   LJMP WDT_ISR                 ; WATCHDOG TIMER (WDT) ISR
	   ORG  0FE33h                  ; PCA INTERRUPT VECTOR LOCATION
	   LJMP ISR_PCA                 ; Jump to PCA Interrupt Handler.

;*************************************************************************

; BASIC call vectors--

	   ORG  0FE50H                  ; Put at very top of code memory
				     ; (must be decreased if code is expanded)

	   AJMP INIT                	; Init routine.
	   AJMP READ_ADC                ; Read A/D Converter
	   AJMP EX_ASYNC                ; Handle change of SP_SYNC.
	   AJMP IAC_HIGHER		; IAC motor init for higher idle
	   AJMP IAC_LOWER		; IAC motor init for lower idle
	   AJMP IAC_STEP		; Step IAC motor in selected direction
	   AJMP IAC_OFF			; Turn off power to IAC motor (doesn't move)

;*************************************************************************

; Startup routines--

    INIT:  				; Init stuff for ASM routines.
 setb p4.0    ;debug
	   MOV	IP,#01000010b           ; Set PPC and PT0 (PCA0 2nd, Timer0 1st)
	   MOV  IE,#11000010b           ; Enable global (EA), PCA (EC) and TIMER0 (ET0) ints.

	   MOV  CMOD,#00               ; Setup PCA Counter Mode. (f.osc/12)
	   MOV  CCON,#01000000b        ; Enable PCA counter (CR)
	   MOV  CCAPM0,#00100001b       ; Set PCA0 Mode: Capture positive
					;  edge and enable PCA interrupt.
	   SETB  SP_SYNC                ; Set flag to sync mode initially
	   ACALL EX_ASYNC               ; Set sync mode (based on flag)

	   MOV  DPTR, #TICK15           ; Clear 2 BASIC counter register
	   MOV  A, #00                  ;   bytes.
	   MOVX @DPTR, A                ;   Clear the first byte...
	   INC DPTR                     ;   then clear the second byte.
	   MOVX @DPTR, A                ; 

	   MOV  ACON,#00010000b         ; Enable A/D Converter

; Setup I/O ports.  Inputs must be set to 1 before they will work.
; See "8051 IO Ports.xls" for specific pin functions.
	   SETB P1.0	; Cranking
	   SETB P1.1	; Key on
	   SETB P1.3	; SP in	   
	   SETB P3.2	; External Int 0
	   SETB P3.4	; A/C on
	   SETB P5.2	; DIP SW 2
	   SETB P5.3	; DIP SW 1

  clr p4.0     ;debug
	   RET

;*************************************************************************

; Main Loop subroutines--

; ASM routine called by BASIC to start or end Async Injection Mode based on
;   Async Mode flag, must be called when ever SP_SYNC is changed.

EX_ASYNC:
;  setb p4.1    ;debug
	   MOV  CCAPM3,#0               ; Disable PCA3.
	   JB   SP_SYNC,EA_OFF          ; Check Sync Mode Flag.
					; Startup Async Mode.
	   CLR  CCF3                    ;    Clear any pending IRQ for PCA3.
	   MOV  CCAP3L,#0               ;    Setup Compare Register with
	   MOV  A,CH                    ;      0.25-0.51 ms from now to start
	   ADD  A,#2                    ;      1st Async pulse.
	   MOV  CCAP3H,A
	   MOV  CCAPM3,#01001001b       ;    Set PCA3 for Compare Mode and 
					;      Enable Interrupt.
EA_OFF:
;    clr p4.1     ;debug
	   RET                          ; Done.


; Read AD Converter and store in mirror locations (ADCMIRR..ADCMIRR+7) since 
; the internal locations which contain the registers are not accesible from
; from BASIC.

READ_ADC:  PUSH ACC
	   PUSH DPL
	   PUSH DPH
	   PUSH PSW

	   MOV  DPTR,#ADC_MIRR          ; Put first mirror address in DPTR
	   MOV  A,ADC_0         ; Read A/D Channel 0
	   MOVX @DPTR,A                 ; Save channel 0 to mirror location
	   MOV  A,ADC_1         ; Read A/D Channel 1
	   INC  DPTR                    ; Increment mirror address
	   MOVX @DPTR,A                 ; Save channel 1 to mirror location
	   MOV  A,ADC_2         ; Read A/D Channel 2
	   INC  DPTR                    ; Increment mirror address
	   MOVX @DPTR,A                 ; Save channel 2 to mirror location
	   MOV  A,ADC_3         ; Read A/D Channel 3
	   INC  DPTR                    ; Increment mirror address
	   MOVX @DPTR,A                 ; Save channel 3 to mirror location
	   MOV  A,ADC_4         ; Read A/D Channel 4
	   INC  DPTR                    ; Increment mirror address
	   MOVX @DPTR,A                 ; Save channel 4 to mirror location
	   MOV  A,ADC_5         ; Read A/D Channel 5
	   INC  DPTR                    ; Increment mirror address
	   MOVX @DPTR,A                 ; Save channel 5 to mirror location
	   MOV  A,ADC_6         ; Read A/D Channel 6
	   INC  DPTR                    ; Increment mirror address
	   MOVX @DPTR,A                 ; Save channel 6 to mirror location
	   MOV  A,ADC_7         ; Read A/D Channel 7
	   INC  DPTR                    ; Increment mirror address
	   MOVX @DPTR,A                 ; Save channel 7 to mirror location

	   POP	PSW
	   POP  DPH
	   POP  DPL
	   POP  ACC
	   RET


;*************************************************************************

; Interrupt Service Routines--

; Interrupt Service Routine for all PCA interrupts.  Determines which
; PCA generated the int. and jumps to the corresponding routine.

ISR_PCA:
	   JBC  CCF0,ISR_PCA0           ; Check & clear flag for PCA0.
	   JBC  CCF1,ISR_PCA1           ;   etc.
	   JBC  CCF3,ISR_PCA3
	   RETI                         ; Others are not used.


; Interrupt Service Routine for End of Injection Pulse -- PCA 1 (Inj 1).
; PCA 2 (Inj 2) is not currently used as an independent timer, but just as a
; single bit output based on the timer used by inj. 1.
ISR_PCA1:  MOV  CCAPM1,#0               ; Disable PCA Module 1. Turn off inj. #1
	   CLR	P1.5			; Turn off Inj. #2
	   RETI                         ; Return from Interrupt.


; Interrupt Service Routine for Starting Async Injection Pulses -- PCA3.
ISR_PCA3:  
 ;setb p4.3 ; debug
	   PUSH PSW                     ; Save registers.
	   PUSH ACC

	   ACALL SETPW                  ; Handle Starting Output Pulse.
	   
	   MOV  A,APP                   ; Set up this PCA for the next Async 
	   ADD  A,CCAP3L                ;   Pulse.
	   MOV  CCAP3L,A                ;    Add Async period to last time
	   MOV  A,APP+1                 ;      for next time.  Also, note
	   ADDC A,CCAP3H                ;      that PCA Compare is disabled
	   MOV  CCAP3H,A                ;      by hardware between write of
					;      low and high CAP bytes.
 ;clr p4.3 ; debug
	   AJMP IP0_RTI                 ; Done, restore registers and return
					;   from interrupt.


; Interrupt Service Routine for Spark Timing (RPM) -- PCA 0.  Also starts
;   Injection Pulse when in Synchronous Mode.

ISR_PCA0:  PUSH PSW                     ; Save registers.
	   PUSH ACC
setb p4.2
	   JNB  SP_SYNC,IP0_RPM         ; If in Async mode, skip output
					;   pulse.

	   ACALL SETPW                  ; Handle Starting Output Pulse.
	   
IP0_RPM:   CLR  C                       ; Compute RPM Pulse Width.
	   MOV  A,CCAP0L                ;    RPMPW = CCAP0 - OLD_CCAP0
	   SUBB A,OLD_CCAP0             ;      (16-bit subtract)
	   MOV  RPMPW,A
	   MOV  A,CCAP0H                ;       Do MSB.
	   SUBB A,OLD_CCAP0+1
	   MOV  RPMPW+1,A
	   MOV  OLD_CCAP0,CCAP0L        ;    Save CCAP0 for next time.
	   MOV  OLD_CCAP0+1,CCAP0H

IP0_RTI:   POP  ACC                     ; Restore registers.
	   POP  PSW
clr p4.2  ; debug
	   RETI                         ; Return from Interrupt.


; Handle Starting an Output Pulse.  Common to ISR_PCA0 & ISR_PCA3.

SETPW:                                  ; Test for zero output pulse width.
 setb p4.4 ; debug
	   MOV  A,PW1                   ;    Get LSB of PW.
	   JNZ  SPW_SETPW               ;    If not zero, setup PW.
	   MOV  A,PW1+1                 ;    Get MSB of PW.
	   JZ   SPW_DONE                ;    If zero, skip PW.
	   MOV  A,PW1                   ;    Get LSB of PW.

SPW_SETPW: 
	   SETB CEX1                    ; Start output pulse. Turn on inj. #1
	   SETB P1.5			; Turn on Inj. #2
	   JNB  SP_SYNC,SPW_ASYN        ; Handle PW for Sync Mode.

SPW_SYNC:  ADD  A,CCAP0L                ;    Setup PCA1 for output pulse
	   MOV  CCAP1L,A                ;      width.  CCAP1 = CCAP0 + PW1
	   MOV  A,PW1+1                 ;      (16-bit add)
	   ADDC A,CCAP0H

SPW_FIN:   MOV  CCAP1H,A                ; Finish both paths.
	   MOV  CCAPM1,#01001101b       ; Set PCA1 for High Speed Output
					;    and enable interrupt. 
 clr p4.4  ;debug
SPW_DONE:  RET                          ; Return from Subroutine.

SPW_ASYN:  ADD  A,CCAP3L                ; Handle PW for Async Mode.
	   MOV  CCAP1L,A                ;    Setup PCA1 for output pulse
	   MOV  A,PW1+1                 ;      width.  CCAP1 = CCAP3 + PW1
	   ADDC A,CCAP3H                ;      (16-bit add)
	   AJMP SPW_FIN                 ;    Go finish.

IAC_HIGHER:		; IAC motor init for higher idle
		CLR	P5.4		; Set step output low
		CLR	P5.5		; Set direction to higher idle
		SETB	P5.6		; Enable IAC (Turn on)
		RET

IAC_LOWER:		; IAC motor init for lower idle
		CLR	P5.4		; Set step output low
		SETB	P5.5		; Set direction to higher idle
		SETB	P5.6		; Enable IAC (Turn on)
		RET

IAC_STEP:		; Step IAC motor in selected direction
		SETB	P5.4		; Set step output high
		NOP			; Delay for 10us 
		NOP			; for step to be initiated (MC3479 - PWCKx)
		NOP
		NOP
		NOP
		NOP
		NOP
		NOP
		NOP
		NOP
		CLR	P5.4		; Set step output low
		RET

IAC_OFF:		; Turn off power to IAC motor (doesn't move)
		CLR	P5.6		; Disable IAC (Turn off)
		CLR	P5.4		; Set step output to low (it should already be low)
		RET

; WDT routines - see Intel appnotes (AB-44)
; Initialize timer 0 for watchdog ISR - see WDT_ISR:
; Note: Each timer 'tick' is osc/12 secs.
WDT_INIT:
	setb p4.5       ;debug
		SETB EA         ; Enable All interrupts
		SETB ET0        ; Enable Timer0 Int
		SETB PT0	; Set Timer0 int to 1st priority (highest) PT0
		MOV IPH,#00000010b	; Set PT0H	

		MOV TMOD, #01   ; Set Timer0 mode to 16-bit, no prescale
		MOV TL0, #67H   ; Set the timer to interrupt (hit FFFF) in 15000 ticks
		MOV TH0, #0C5H  ; FFFF-3A98 = C567 (65535-15000 = 50535)

		SETB TR0        ; Start the timer

	clr p4.5        ;debug
		RET

	
; This ISR has 3 functions:
;       1) To reset the WDT before 16.3667 ms passes (at 12 MHz)
;       2) To check for rapid TPS movement
;       3) To increment a byte for use as a counter for EGO and related routines

; WDT reset - WDT needs to be reset every 16.3667ms or it will reset the CPU
; Timer 0 is used to call this ISR every 15ms to do this reset.

WDT_ISR:
setb p4.6        ;debug

	PUSH    DPH
	PUSH    DPL
	PUSH    ACC
	PUSH	PSW

	CLR TR0                 ; stop timer 0
	MOV WDTRST, #1EH        ; clear WDT
	MOV WDTRST, #0E1H
	MOV TL0, #67H           ; Set the timer to interrupt (hit FFFF) in 15000 ticks
	MOV TH0, #0C5H          ; FFFF-3A98 = C567 (65535-15000 = 50535)
	SETB TR0                ; restart timer 0

; Pulse bit for external WDT/reset IC.  Inverts every time through.
; This should NOT be kept in the ISR, it needs to be in the main BASIC loop
	CPL P1.6		; Invert Reset IC's WDT bit

; Increment BASIC counter bytes
	   MOV  DPTR, #TICK15           ; Get counter address
	   MOVX A, @DPTR                ; Put the contents of TICK15 in A (LSB)
	   INC  A                       ; Increment it
	   MOVX @DPTR, A                ; Put it back in TICK15
	   JNZ  WDT_EXIT                ; If it hasn't rolled over to 00, then exit
	   INC DPTR                     ; Do the MSB
	   MOVX A, @DPTR

	   MOV  A, #00                  ; 
	   MOVX A, @DPTR                ; Put the contents of TICK15+1 in A (MSB)
	   INC  A                       ; Increment it
	   MOVX @DPTR, A                ; Put it back in TICK15+1

WDT_EXIT:       
		POP	PSW
		POP     ACC
		POP     DPL
		POP     DPH

clr p4.6       ;debug
		RETI

	

	   END

--=====================_4473098==_
Content-Type: text/plain; charset="us-ascii"


--=====================_4473098==_--




More information about the Diy_efi mailing list