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

📄 lc2.asm

📁 another LC meter using a p16f628 single chip,it work well for measure LC.
💻 ASM
📖 第 1 页 / 共 2 页
字号:
;*******************************************************************
;
;	Inductance & Capacitance Meter with Software calibration
;
;*******************************************************************
;
;	First, let us choose our weapon - a 16F628
;
;*******************************************************************
;
; LC002	- THIS ONE WORKS FINE WITH A WELL BEHAVED DISPLAY
;
;	Deleted  CpyBin subroutine and one call to it
;
;	Modified B2_BCD to take its input directly from <AARGB0,1,2>
;
;	Modified "oscillator test" so it copies F3   to <AARGB0,1,2>
;
;	Fixed Get_Lcal so it gets the correct number
;
;	Minor adjustment to MS100 timing to correct frequency display
;
;	Check for oscillator too slow when measuring L or C.
;
;
;*******************************************************************
;
; LC003	- Optimised / Modified to handle "bad" displays
;
;	Removed duplicated code in DATS subroutine
;
;	Added code to fix crook display (select by jumper on B4 - 10)
;
;	Optimised L & C formatting code
;
;	Optimised "Display" subroutine
;
;	Cleaned up LCDINIT
;
;
;*******************************************************************
;
; LC004 - Deleted timer Interrupt Service Routine
;
;	Modified way oscillator "out of range" condition is detected
;
;
;*******************************************************************
;
; LC628 - LC004 code ported to 16F628 by Egbert Jarings PA0EJH.
;	Mem starts now at 0x20
;	InitIO modified , 628 PortA start's up in Analog Mode 
;	So changed to Digital Mode (CMCON)
; 
;	Display's "Calibrating" to fill up dead Display time
;	when first Powerd Up.
;
;	Changed pmsg Routine, EEADR  trick  wont work with 628,
;	PCL was always 0x00 so restart occurs. EEADR is now Etemp.
;
;	Also changed EEADR in FP routine to Etemp 
;
;	Bad Display isn't bad at all, its a Hitachi HD44780, as
;	80% of all Display's are. Adress as 2 Lines x 8 Char.
;	So LCDINIT modified for 2 x 8 Display's. (0x28 added)
;
;*******************************************************************
;
; LC005 - Cosmetic rewrite of RAM allocation from LC004
;
;	No change to address of anything - I hope
;	Identified unused RAM & marked for later removal.
;
;
;*******************************************************************
;
; LC006 - Merge LC005 and LC628
;
;	All "#ifdef" F628 parts by Egbert Jarings PA0EJH.
;	(or derived from his good work)
;
;	Cleaned up RAM allocation.
;
;	Added message re: processor type, just to verify selection
;
;	Included extra initialisation (2 line) command by PA0EJH
;
;*******************************************************************
;
; lc007	Changed strings to EEPROM (it's not used for anything else)
;
;	Added "error collector" code to catch "all" FP errors
;
;       Addded macros
;
;
;*******************************************************************
;
; LC_swcal.000
;	Changed to use only F628 processor
;	Used internal comparator of F628 in place of LM311
;	Switched relay directly by digital I/O
;	Implemented software calibration via constant in EEPROM
;	Re-allocated most I/O pins
;	Added output munger for LCD connections (easy to re-allocate)
;
;
;*******************************************************************
;o-----o-----o-----o-----o-----o-----o-----o-----o-----o-----o-----o
;*******************************************************************
;
;	Some frequently used code fragments
;	Use macros to make mistreaks consistently.
;
;-------------------------------------------------------------------
;	Select Register Bank 0

bank0	macro
	errorlevel	+302		; Re-enable bank warning
	bcf		STATUS,RP0	; Select Bank 0
	endm

;-------------------------------------------------------------------
;	Select Register Bank 1

bank1	macro
	bsf		STATUS,RP0	; Select Bank 1
	errorlevel	-302		; disable warning
	endm

;-------------------------------------------------------------------
;	Swap bytes in register file via W

swap	macro	this,that

	movf	this,w		; get this
	xorwf	that,f		; Swap using Microchip
	xorwf	that,w		; Tips'n Tricks
	xorwf	that,f		; #18
	movwf	this

	endm

;-------------------------------------------------------------------
;	Copy bytes in register file via W

copy	macro	from,to

	MOVF	from,W
	MOVWF	to

	endm

;*******************************************************************
;
;	CPU configuration
;

	MESSG		"Processor = 16F628"
	processor	16f628
	include		<p16f628.inc>
	__CONFIG        _CP_OFF & _WDT_OFF & _PWRTE_ON & _HS_OSC & _BODEN_ON & _LVP_OFF

;**********************************************************
;
;	I/O Assignments.
;

#define	LCD0	PORTB,3
#define	LCD1	PORTB,2
#define	LCD2	PORTB,1
#define	LCD3	PORTB,0
#define	ENA	PORTB,4		; Display "E"
#define	RS	PORTB,5		; Display "RS"
#define	functn	PORTB,6		; 0 = "Inductor"
#define relay	PORTB,7		; Switches Ccal

;*******************************************************************
;
;	file register declarations: uses only registers in bank0
;	bank 0 file registers begin at 0x0c in the 16F84
;	and at 0x20 in the 16F628
;
;*******************************************************************

	cblock	0x20
;
;       Floating Point Stack and other locations used by FP.TXT
;
;	FP Stack: TOS	A = 	AEXP:AARGB0:AARGB1:AARGB3:AARGB4
;			B = 	BEXP:BARGB0:BARGB1:BARGB2
;			C = 	CEXP:CARGB0:CARGB1

	AARGB4
	AARGB3
	AARGB2
	AARGB1
	AARGB0
	AEXP			; 8 bit biased exponent for argument A
	SIGN			; save location for sign in MSB

	FPFLAGS			; floating point library exception flags
	
	BARGB2
	BARGB1
	BARGB0
	BEXP			; 8 bit biased exponent for argument B

	TEMPB3			; 1 Unused byte
	TEMPB2			; 1 Unused byte
	TEMPB1			; Used
	TEMPB0			; 1 Unused byte

	CARGB1
	CARGB0			; most significant byte of argument C
	CEXP			; 8 bit biased exponent for argument C

;
;	"Main" Program Storage
;
 
	COUNT			; Bin to BCD convert (bit count)
	cnt			;                    (BCD BYTES)

	CHR 

	F1:2
	F2:2
	F3:2
	
	bcd:4			; BCD, MSD first 

	TabStop			; Used to fix bad displays.
	TabTemp

	FPE			; Collect FP errors in here
	
	R_sign			; Holds "+" or " " (sign)

	EEflag:1		; Cal adjust flag
	
	endc

	cblock	0x70		; Common RAM

	cal_t:2			; Ccal temporary value

	PB_data:1		; LCD output munger temp
	
	links:1			; User test links copy

	COUNT1			; Used by delay routines
				; and "prescaler flush"
	COUNT2			; Timing (100ms)

	endc

EXP	equ	AEXP		; Used by FP.TXT
TEMP	equ	TEMPB0
;AARG	equ	AARGB0		; Unused
;BARG	equ	BARGB0		; Unused
;CARG	equ	CARGB0		; Unused

;*******************************************************************
;
;       GENERAL MATH LIBRARY DEFINITIONS
;
;
;	define assembler constants

B0		equ	0
B1		equ	1
B2		equ	2
B3		equ	3
B4		equ	4
B5		equ	5
B6		equ	6
B7		equ	7

MSB		equ	7
LSB		equ	0

;     STATUS bit definitions

#define	_C	STATUS,0
#define	_Z	STATUS,2

;*******************************************************************
;
;       FLOATING POINT literal constants
;

EXPBIAS         equ     D'127'

;
;       floating point library exception flags
;

IOV             equ     0       ; bit0 = integer overflow flag

FOV             equ     1       ; bit1 = floating point overflow flag

FUN             equ     2       ; bit2 = floating point underflow flag

FDZ             equ     3       ; bit3 = floating point divide by zero flag

NAN		equ	4	; bit4 = not-a-number exception flag

DOM		equ	5	; bit5 = domain error exception flag

RND             equ     6       ; bit6 = floating point rounding flag, 0 = truncation
                                ; 1 = unbiased rounding to nearest LSB

SAT             equ     7       ; bit7 = floating point saturate flag, 0 = terminate on
                                ; exception without saturation, 1 = terminate on
                                ; exception with saturation to appropriate value

;**********************************************************
;
;	Motorola syntax branches
;

#define	beq	bz 
#define	BEQ	bz
#define	BNE	bnz
#define	bne	bnz

#define	BCC	bnc
#define	bcc	bnc
#define	BCS	bc
#define	bcs	bc

#define	BRA	goto
#define	bra	goto


;**********************************************************
;
;	Begin Executable Stuff(tm)
;

	org	0

GO	clrwdt			; 0 << Reset
	call	InitIO
	bcf	relay		; Remove Ccal

;**********************************************************
;
;	Main Program
;

START	CALL	LCDINIT	 	; INITIALIZE LCD MODULE	
	call	EE_RD		; Retrieve CCal integer value

cmdloop	call	HOME

;
;	"Zero" the meter.
;

Chk4Z	MOVLW   Calibr-0x2100	; Display's " Calibrating "
	call	pmsg		; to entertain the punters

	call	Measure		; Dummy Run to stabilise oscillator.
	call	MS200

	call	Measure		; Get freq in F3

	copy	F3+0,F1+0	; Copy F3 to F1
	copy	F3+1,F1+1

	bsf	relay		; Add standard capacitor
	call	MS200

	call	Measure		; Get freq in F3

	copy	F3+0,F2+0	; Copy F3 to F2
	copy	F3+1,F2+1
	
	bcf	relay		; Remove standard capacitor
	call	MS200

	call	Measure		; Dummy Run to stabilise oscillator.

;
;	Now we resume our regular pogrom
;	Read state of user test links on LCD bus
;

M_F3	bank1			; PORTB:-
	movlw	b'01001111'	; LCD data bits to read
	movwf	TRISB		; 1 = input
	bank0			; 0 = output

	call	MS2		; Settling time
	copy	PORTB,links

	bank1
	movlw	b'01000000'	; restore data direction
	movwf	TRISB		; 1 = input
	bank0			; 0 = output

;---------------------------------------------------------------
;
;	Take a break from regular duties to do something interesting
;
	btfss	links,0		; Raise Ccal value
	goto	cal_up

	btfss	links,1		; Lower Ccal value
	goto	cal_dn

	btfss	links,2		; Test osc without Ccal
	goto	osc1

	btfss	links,3		; Test osc with Ccal
	goto	osc2

;
;	None of the above
;

	bcf	relay		; In case of osc test
	btfss	EEflag,0	; Time to save Ccal value?
	goto	cont		; No. Back to work
	
	bcf	EEflag,0	; To say we have done it
	call	EE_WR		; So, we better save it
	goto	cont		; Hi Ho, its off to work I go

;
;	Add +10 to cal_t:2
;

cal_up	bsf	EEflag,0	; Say "we're adjusting"
	movlw	0x0a		; +10
	addwf	cal_t+1,f
	bcc	cont
	
	incf	cal_t+0,f
	goto cont

;
;	Add -10 to cal_t:2
;

cal_dn	bsf	EEflag,0	; Say "we're adjusting"
	movlw	0xf6		; -10
	addwf	cal_t+1,f
	bcc	hi_byte
	
	incf	cal_t+0,f

hi_byte	movlw	0xff
	addwf	cal_t+0,f
	goto	cont		

;
;	Measure & display osc freq for initial setup
;

osc2	bsf	relay		; Add Ccal
	
osc1	call	HOME
	call	Measure		; Measure Local Osc Freq.
	call	CLEAR

	btfss	INTCON,T0IF	; Set = Counter overflow?
	goto	Do_Disp

	MOVLW	ovr-0x2100	; Over-range message
	call	pmsg
	goto	M_F3
	
Do_Disp	clrf	AARGB0		; Copy to 24 bit number
	movf	F3,W		; in AARGB0, 1, 2
	movwf	AARGB1		; for display
	movf	F3+1,W
	movwf	AARGB2

	call	Display
	goto	M_F3

;---------------------------------------------------------------

cont	call	HOME
	call	MS200
	call	Measure		; Measure F3 & leave it there

	movf	F3,w		; test for "too low" frequency
	beq	OORange		; F < 2560Hz ?
	
	btfss	INTCON,T0IF	; test for "too high" frequency
	goto	OK2GO		; F > 655359Hz ?

OORange	MOVLW	ovr-0x2100	; Over/Under range message
	call	pmsg
	
	goto	M_F3

;
;	Precompute major bracketed terms cos
;	we need 'em both for all calculations
;

OK2GO	clrf	FPE		; Declare "error free"
	call	F1_F2
	call	F1_F3

;
;	See what mode we are in
;

	btfss	functn		; 0=Inductor
	goto	Do_Ind

;
;	OK, we've been told it's a capacitor
;

Do_Cap	call	C_calc
	movf	FPE,f		; Any FP errors?
	bne	complain
	
	movlw	Cintro-0x2100	; C =
	call	pmsg

	call	C_disp
	goto	M_F3

;
;	Now, they reckon it's a @#$*! inductor
;

Do_Ind	call	L_calc
	movf	FPE,f		; Any FP errors?
	bne	complain
	
	movlw	Lintro-0x2100	; L =
	call	pmsg

	call	L_disp
	goto	M_F3

;
;	Got a Floating Point Error of some sort
;

complain	movlw	ovr-0x2100	; Over Range
		call	pmsg
	
		goto	M_F3

;**********************************************************
;
;	Print String addressed by W
;	Note: Strings are in EEPROM
;	We do a lotta bank switching here.

pmsg	bank1
	movwf	EEADR		; pointer

pm1	BSF     EECON1,RD       ; EE Read
        MOVF    EEDATA,W        ; W = EEDATA, affects Z bit
        bank0			; Does not change Z bit
 
	btfsc	STATUS,Z	; ZERO = All done
	return			; so quit

	call	DATS		; Byte -> display

	bank1
	INCF    EEADR,F         ; bump address
	goto	pm1

;**********************************************************
;
;	Delay for 2ms (untrimmed)
;

MS2	MOVLW	0xFD		; DELAY 2ms
	MOVWF	COUNT1

	MOVLW	0x66
	MOVWF	COUNT2

	goto	L3		

;**********************************************************
;
;	Delay for about 200ms or 300ms (untrimmed)
;

MS300	call	MS100

MS200	call	MS100

;**********************************************************
;
;	Delay for about 100ms
;

MS100	MOVLW	0x7e		; Count up
	MOVWF	COUNT1		; to roll-over

	MOVLW	0x20		; was 0x19, then 0x25, then 1f
	MOVWF	COUNT2			

L3	INCFSZ	COUNT2,F
	GOTO	L3

	INCFSZ	COUNT1,F
	GOTO	L3

	RETLW	0

;**********************************************************
;
;	Put a BCD nybble to display
;

PutNyb	ANDLW	0x0F		; MASK OFF OTHER PACKED BCD DIGIT
	ADDLW	0x30		; Convert BIN to ASCII

;**********************************************************
;
;	Put a byte to display
;

DATS	decf	TabStop,F	; Time to tickle bad display?
	bne	DAT1		; Not yet
	
	movwf	TabTemp		; Save character
	
;	btfss	FIXIT		; Check if we got a crook one.
;	CALL	LINE2		; Skip this if good

	movf	TabTemp,W	; Restore character

DAT1	BSF	RS		; SELECT DATA REGISTER
CM	MOVWF	CHR		; STORE CHAR TO DISPLAY
	SWAPF	CHR,W		; SWAP UPPER AND LOWER NIBBLES (4 BIT MODE)

	call	PB_dly

	MOVF	CHR,W		; GET CHAR AGAIN 

;**********************************************************
;
;	Put 4 bits to LCD & wait (untrimmed)
;

PB_dly	movwf	PB_data		; Save nybble

	btfss	PB_data,0	; copy LSbit
	bcf	LCD0
	btfsc	PB_data,0
	bsf	LCD0
	
	btfss	PB_data,1
	bcf	LCD1
	btfsc	PB_data,1
	bsf	LCD1
	
	btfss	PB_data,2
	bcf	LCD2
	btfsc	PB_data,2
	bsf	LCD2
	
	btfss	PB_data,3	; copy MSbit
	bcf	LCD3
	btfsc	PB_data,3
	bsf	LCD3
	
	BSF	ENA		; ENA HIGH
	NOP			
	BCF	ENA		; ENA LOW 

;	goto	D200us		; Fall into DELAY subroutine

;**********************************************************
;
;	Delay for 200us (untrimmed)
;

⌨️ 快捷键说明

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