0% found this document useful (0 votes)
297 views22 pages

LC Meter 007

This document contains code for an inductance and capacitance meter. It defines macros and constants used in the code. It initializes the ports and LCD display. The main loop measures the oscillator frequency, displays it, and determines if it is in range. It then determines if the mode is capacitor or inductor and performs the appropriate calculations. It handles floating point errors. Strings are stored in EEPROM and printed with a subroutine that handles bank switching.

Uploaded by

yooo2011
Copyright
© Attribution Non-Commercial (BY-NC)
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as TXT, PDF, TXT or read online on Scribd
0% found this document useful (0 votes)
297 views22 pages

LC Meter 007

This document contains code for an inductance and capacitance meter. It defines macros and constants used in the code. It initializes the ports and LCD display. The main loop measures the oscillator frequency, displays it, and determines if it is in range. It then determines if the mode is capacitor or inductor and performs the appropriate calculations. It handles floating point errors. Strings are stored in EEPROM and printed with a subroutine that handles bank switching.

Uploaded by

yooo2011
Copyright
© Attribution Non-Commercial (BY-NC)
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as TXT, PDF, TXT or read online on Scribd
You are on page 1/ 22

;******************************************************************* ; ; Inductance & Capacitance Meter ; ;******************************************************************* ; ; First, let us choose our weapon - 16F84 or 16F628 ; ; Comment out

the next line [;#define F84] if using a 16F628

#define F84 #ifndef F84 #define F628 #endif ;******************************************************************* ; ; 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 ; ; ;******************************************************************* ;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 bcf endm +302 STATUS,RP0 ; Re-enable bank warning ; Select Bank 0

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

;------------------------------------------------------------------; Swap bytes in register file via W swap macro movf xorwf xorwf xorwf movwf endm ;------------------------------------------------------------------; Copy bytes in register file via W copy macro MOVF MOVWF endm ;******************************************************************* ; ; CPU configuration ; #ifdef F84 MESSG #define processor include __config #endif #ifdef F628 MESSG #define processor include __CONFIG LVP_OFF #endif "Processor = 16F84" RAMStart 0x0C ; by VK3BHR 16f84 <p16f84.inc> _HS_OSC & _PWRTE_ON & _WDT_OFF from,to from,W to this,that this,w that,f that,w that,f this ; ; ; ; get this Swap using Microchip Tips'n Tricks #18

"Processor = 16F628" RAMStart 0x20 ; by PA0EJH 16f628 <p16f628.inc> _CP_OFF & _WDT_OFF & _PWRTE_ON & _HS_OSC & _BODEN_ON & _

;********************************************************** ; ; I/O Assignments. Luckily, the same assignments ; work on both the 16F84 and the 16F628. ;

#define ENA #define RS #define relay #define FIXIT #define setup

PORTA,0x02 PORTA,0x03 PORTA,0x01 PORTB,0x04 PORTB,0x06

; Display "E" ; Display "RS" ; 0 = energise relay ; Pin 10, 0 = "fix bad display" ; Floating 1 = "good display" ; Pin 12, 0 = "Setup" ; Pin 13, 0 = "Inductor"

#define functn PORTB,0x07

;******************************************************************* ; ; 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 RAMStart ; ; ; ; ; ; Floating Point Stack and other locations used by FP.TXT FP Stack: TOS A = B = C = AEXP:AARGB0:AARGB1:AARGB3:AARGB4 BEXP:BARGB0:BARGB1:BARGB2 CEXP:CARGB0:CARGB1

AARGB4 AARGB3 AARGB2 AARGB1 AARGB0 AEXP SIGN FPFLAGS BARGB2 BARGB1 BARGB0 BEXP TEMPB3 TEMPB2 TEMPB1 TEMPB0 CARGB1 CARGB0 CEXP ; ; ; "Main" Program Storage COUNT cnt

; 8 bit biased exponent for argument A ; save location for sign in MSB ; floating point library exception flags

; 8 bit biased exponent for argument B ; ; ; ; 1 Unused byte 1 Unused byte Used 1 Unused byte

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

; Bin to BCD convert (bit count) ; (BCD BYTES)

COUNT1 COUNT2 CHR F1:2 F2:2 F3:2 bcd:4 TabStop TabTemp FPE R_sign endc EXP TEMP ;AARG ;BARG ;CARG equ equ equ equ equ AEXP TEMPB0 AARGB0 BARGB0 CARGB0

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

; BCD, MSD first ; Used to fix bad displays. ; Collect FP errors in here ; Holds "+" or " " (sign)

; Used by FP.TXT ; Unused ; Unused ; Unused

;******************************************************************* ; ; GENERAL MATH LIBRARY DEFINITIONS ; ; ; define assembler constants B0 B1 B2 B3 B4 B5 B6 B7 MSB LSB ; equ equ equ equ equ equ equ equ equ equ 0 1 2 3 4 5 6 7 7 0

STATUS bit definitions STATUS,0 STATUS,2

#define _C #define _Z

;******************************************************************* ; ; FLOATING POINT literal constants ; EXPBIAS ; ; equ D'127'

floating point library exception flags

; IOV FOV FUN FDZ NAN DOM RND ation SAT nate on equ equ equ equ equ equ equ 0 1 2 3 4 5 6 ; bit0 = integer overflow flag ; bit1 = floating point overflow flag ; bit2 = floating point underflow flag ; bit3 = floating point divide by zero flag ; bit4 = not-a-number exception flag ; bit5 = domain error exception flag ; bit6 = floating point rounding flag, 0 = trunc ; 1 = unbiased rounding to nearest LSB equ 7 ; bit7 = floating point saturate flag, 0 = termi ; exception without saturation, 1 = terminate on ; exception with saturation to appropriate value ;********************************************************** ; ; Motorola syntax branches ; #define #define #define #define #define #define #define #define beq BEQ BNE bne BCC bcc BCS bcs bz bz bnz bnz bnc bnc bc bc goto goto

#define BRA #define bra

;********************************************************** ; ; Begin Executable Stuff(tm) ; org GO ; 0 ; ; ; ; 0 << Reset 1 INITIALISE PORTS 2 3

clrwdt call InitIO CLRF PORTA goto START

;********************************************************** ; ; Main Program ; START bsf relay ; de-energise relay

CLRF CALL cmdloop call btfsc goto ; ; ;

PORTB LCDINIT HOME setup Chk4Z ; Doing initial oscillator test? ; INITIALIZE LCD MODULE

Measure & display osc freq for initial setup call btfss goto MOVLW call goto Measure INTCON,T0IF Do_Disp ovr-0x2100 pmsg cmdloop AARGB0 F3,W AARGB1 F3+1,W AARGB2 Display cmdloop ; Copy to 24 bit number ; in AARGB0, 1, 2 ; for display ; Measure Local Osc Freq. ; Set = Counter overflow? ; Over-range message

Do_Disp clrf movf movwf movf movwf call goto ; ; ; Chk4Z

"Zero" the meter. MOVLW call call call call copy copy bcf call call copy copy bsf call Calibr-0x2100 pmsg Measure MS200 Measure F3+0,F1+0 F3+1,F1+1 relay MS200 Measure F3+0,F2+0 F3+1,F2+1 relay MS200 ; Display's " Calibrating " ; to entertain the punters ; Dummy Run to stabilise oscillator. ; was MS300 ; Get freq in F3 ; Copy F3 to F1 ; Add standard capacitor ; Get freq in F3 ; Copy F3 to F2 ; Remove standard capacitor

; ; M_F3

Now we resume our regular pogrom call call movf beq btfss goto HOME Measure F3,w OORange INTCON,T0IF OK2GO ovr-0x2100 pmsg M_F3

; Measure F3 & leave it there ; test for "too low" frequency ; F < 2560Hz ? ; test for "too high" frequency ; F > 655359Hz ? ; Over/Under range message

OORange MOVLW call goto ; ; ; ; OK2GO

Precompute major bracketed terms cos we need 'em both for all calculations clrf call call FPE F1_F2 F1_F3 ; Declare "error free"

; ; ;

See what mode we are in btfss goto functn Do_Ind ; 0=Inductor

; ; ;

OK, we've been told it's a capacitor C_calc FPE,f complain Cintro-0x2100 pmsg C_disp M_F3

Do_Cap call movf bne movlw call call goto ; ; ;

; Any FP errors? ; C =

Now, they reckon it's a @#$*! inductor L_calc FPE,f complain Lintro-0x2100 pmsg L_disp M_F3

Do_Ind call movf bne movlw call call goto

; Any FP errors? ; L =

; ; ;

Got a Floating Point Error of some sort movlw call goto ovr-0x2100 pmsg M_F3 ; Over Range

complain

;********************************************************** ; ; Print String addressed by W ; Note: Strings are in EEPROM ; We do a lotta bank switching here. #ifdef F84 pmsg pm1 movwf bank1 BSF bank0 EEADR EECON1,RD ; pointer ; EE Read ; W = EEDATA, affects Z bit ; ZERO = All done ; so quit ; Byte -> display ; bump address

MOVF EEDATA,W btfsc STATUS,Z return call INCF goto #endif DATS EEADR,F pm1

;----------------------------------------------------------#ifdef F628 pmsg pm1 bank1 movwf BSF MOVF bank0 EEADR EECON1,RD EEDATA,W ; pointer ; EE Read ; W = EEDATA, affects Z bit ; Does not change Z bit ; ZERO = All done ; so quit ; Byte -> display ; bump address

btfsc STATUS,Z return call bank1 INCF goto #endif DATS EEADR,F pm1

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

; MS2 MOVLW MOVWF MOVLW MOVWF goto 0xFD COUNT1 0x66 COUNT2 L3 ; DELAY 2ms

;********************************************************** ; ; Delay for about 200ms or 300ms (untrimmed) ; MS300 MS200 call call MS100 MS100

;********************************************************** ; ; Delay for about 100ms ; MS100 MOVLW MOVWF MOVLW MOVWF L3 0x7e COUNT1 0x20 COUNT2 ; Count up ; to roll-over ; was 0x19, then 0x25, then 1f

INCFSZ COUNT2,F GOTO L3 INCFSZ COUNT1,F GOTO L3 RETLW 0

;********************************************************** ; ; Put a BCD nybble to display ; PutNyb ANDLW ADDLW 0x0F 0x30 ; MASK OFF OTHER PACKED BCD DIGIT ; Convert BIN to ASCII

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

DAT1 CM

BSF MOVWF SWAPF call MOVF

RS CHR CHR,W PB_dly CHR,W

; SELECT DATA REGISTER ; STORE CHAR TO DISPLAY ; SWAP UPPER AND LOWER NIBBLES (4 BIT MODE)

; GET CHAR AGAIN

;********************************************************** ; ; Put 4 bits to LCD & wait (untrimmed) ; PB_dly ANDLW MOVWF BSF NOP BCF ; goto 0x0F PORTB ENA ENA D200us ; MASK OFF UPPER 4 BITS ; SEND DATA TO DISPLAY ; ENA HIGH ; ENA LOW ; Fall into DELAY subroutine

;********************************************************** ; ; Delay for 200us (untrimmed) ; D200us MOVLW MOVWF NXT5 DECFSZ GOTO RETLW 0x42 COUNT1 COUNT1,F NXT5 0 ; DELAY 200us

;****************************************************************** ; ; Convert 24-bit binary number at <AARGB0,1,2> into a bcd number ; at <bcd>. Uses Mike Keitz's procedure for handling bcd ; adjust; Modified Microchip AN526 for 24-bits. ; B2_BCD b2bcd movlw movwf clrf clrf clrf clrf b2bcd2 movlw movwf movlw movwf .24 COUNT bcd+0 bcd+1 bcd+2 bcd+3 bcd FSR .4 cnt ; 24-bits ; make cycle counter ; clear result area

; make pointer

; Mike's routine: b2bcd3 movlw addwf btfsc andlw 0x33 INDF,f INDF,3 0xf0 ; add to both nybbles ; test if low result > 7 ; low result >7 so take the 3 out

btfsc andlw subwf incf decfsz goto rlf rlf rlf rlf rlf rlf rlf

INDF,7 0x0f INDF,f FSR,f cnt,f b2bcd3 AARGB2,f AARGB1,f AARGB0,f bcd+3,f bcd+2,f bcd+1,f bcd+0,f

; ; ; ;

test if high result > 7 high result > 7 so ok any results <= 7, subtract back point to next

; get another bit

; put it into bcd

decfsz COUNT,f goto b2bcd2 return

; all done? ; no, loop ; yes

;*********** INITIALISE LCD MODULE 4 BIT MODE *********************** LCDINIT CALL BCF BCF MOVLW call CALL MOVLW call MOVLW call MOVLW call MOVLW CALL MOVLW CALL MOVLW CALL MS100 RS ENA 0x03 PB_dly MS100 0x03 PB_dly 0x03 PB_dly 0x02 PB_dly 0x0C ST200us 0x28 ST200us 0x06 ST200us ; WAIT FOR LCD MODULE HARDWARE RESET ; REGISTER SELECT LOW ; ENABLE LINE LOW ; 1 ; WAIT FOR DISPLAY TO CATCH UP ; 2 ; 3 ; Fn set 4 bits ; 0x0C DISPLAY ON ; DISPLAY 2 Line , 5x7 Dot's ; New in LC628/LC006 version ; 0x06 ENTRY MODE SET ; Fall into CLEAR

;************ CLEAR DISPLAY *************************** CLEAR MOVLW goto 0x01 Home2 ; CLEAR DISPLAY ; LONGER DELAY NEEDED WHEN CLEARING DISPLAY

;*********** MOVE TO HOME ***************************** HOME movlw movwf 0x09 TabStop ; Count characters ; before tickling display.

Home2

MOVLW CALL goto

0x02 STROBE MS2

; HOME DISPLAY

;********************************************************** ; ; SENDS DATA TO LCD DISPLAY MODULE (4 BIT MODE) ; STROBE BCF GOTO RS CM ; SELECT COMMAND REGISTER

;************ MOVE TO START OF LINE 2 ***************** LINE2 MOVLW 0xC0 STROBE D200us ; ADDRESS FOR SECOND LINE OF DISPLAY

ST200us CALL goto

;******************************************************************** ; Initialise Input & Output devices ;******************************************************************** InitIO #ifdef F628 BSF CMCON,CM0 BSF CMCON,CM1 BSF CMCON,CM2 #endif bank1 movlw movwf 0x37 OPTION_REG ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; ; Option register Port B weak pull-up enabled INTDEG Don't care Count RA4/T0CKI Count on falling edge Prescale Timer/counter divide Timer/counter by 256 PORTA:initialise data direction 1 = input 0 = output PORTA has 5 pins 4 3 2 1 0 0x10 = 0 0 0 1 0 0 0 0 PORTA<0> PORTA<1> PORTA<2> PORTA<3> PORTA<4> PORTA<5:7> = = = = = = CLAMP count input Relay. 0 = energise LCD "E" LCD "RS" Count Input not implemented in 16F84

; By PA0EJH ; Set Comp to digital I/O ;

movlw

0x10

movwf

TRISA

movlw

0xf0

PORTB:initialise data direction

movwf

TRISB

; ; ; ; ; ; ; ; ; ; ; ;

PORTB has 8 pins port pin 7 6 5 4 3 2 1 0 0xf0 = 1 1 1 1 0 0 0 0 PORTB<0> PORTB<1> PORTB<2> PORTB<3> PORTB<4> PORTB<5> PORTB<6> PORTB<7> = = = = = = = = LCD "DB4" "DB5" "DB6" "DB7" Input Input Input Input

bank0 return ;********************************************************** ; ; Measure Frequency. Stash in "F3 and F3+1" ; Measure bcf CLRF bsf CLRF CLRF INTCON,T0IF TMR0 PORTA,0 F3 F3+1 ; Declare "Not yet Over-range" ; RESET INTERNAL COUNT (INCLUDING PRESCALER) ; See page 27 Section 6.0 ; Part of Osc gating ; Ready to receive 16 bit number ; OPEN GATE bank1 movlw 0x11 ; ; ; ; PORTA:initialise data direction 1 = input 0 = output

; PORTA has 5 pins 4 3 2 1 0 ; 0x10 = 0 0 0 1 0 0 0 1 movwf TRISA ; ; ; ; ; ; PORTA<0> PORTA<1> PORTA<2> PORTA<3> PORTA<4> PORTA<5:7> = = = = = =

LCD "E" LCD "RS" Input not implemented in 16F84

CALL

MS100

; 100MS DELAY ; CLOSE GATE (COUNT COMPLETE)

movlw

0x10

; ; ; ;

PORTA:initialise data direction 1 = input 0 = output 4 3 2 1 0

; PORTA has 5 pins

; 0x10 movwf TRISA ; ; ; ; ; ; PORTA<0> PORTA<1> PORTA<2> PORTA<3> PORTA<4> PORTA<5:7>

= = = = = = =

0 0 0 1 0 0 0 0

LCD "E" LCD "RS" Input not implemented in 16F84

bank0 MOVF MOVWF TMR0,W F3 ; GET HIGH BYTE ; Copy to Big end of 16 bit result

; The 311 "outputting" a 1 'cos we've forced it high ; so T0CKI=1. PSC1 bank1 bsf nop bcf bank0 DECF movf xorwf beq return OPTION_REG,T0SE ; Clock the prescaler OPTION_REG,T0SE F3+1,F TMR0,W F3,W PSC1 ; F3 : F3+1 now holds 16 bit result ; Decrement the counter ; Has TMR0 changed? ; if unchanged, XOR -> 0

;********************************************************** ; ; Display contents of AARGB0,1,2 on LCD ; First convert to BCD, Then ASCII (nybble at a time) ; Display CALL call call call call call call call goto B2_BCD Swap0 Move0 Swap1 Move1 Swap2 Move2 Swap3 Move3 ; CONVERT COUNT TO BCD ; GET NEXT DIGIT ; GET OTHER BCD DIGIT

; includes return

;********************************************************** ; ; Formatted display of BCD work area for Capacitor ; C_disp movf call F_C1 MOVF ANDLW beq R_sign,w DATS bcd+0,W 0x0F F_C2 ; Sign

CALL call call CALL call goto

PutNyb Swap1 Move1 DoDP Swap2 F_C3U

; Print DP

;-------------------------------------------------F_C2 swapf ANDLW beq CALL call CALL call call goto bcd+1,W 0x0F F_C3 PutNyb Move1 DoDP Swap2 Move2 F_C3U

; Print DP ; print nF. includes RETURN

;-------------------------------------------------F_C3 MOVF ANDLW beq CALL CALL call call call F_C3U movlw goto bcd+1,W 0x0F F_C4 PutNyb DoDP Swap2 Move2 Swap3 Unit1-0x2100 pmsg ; Print DP

; nF ; includes RETURN

;-------------------------------------------------F_C4 SWAPF ANDLW bne MOVLW call MOVF ANDLW bne MOVLW call bra NoB1_C call NoB2_C call NoB3_C call CALL call movlw goto bcd+2,W 0x0F NoB1_C 0x20 DATS bcd+2,W 0x0F NoB2_C 0x20 DATS NoB3_C Swap2 Move2 Swap3 DoDP Move3 Unit2-0x2100 pmsg ; Digit1 == 0 ?

; YES PRINT A SPACE ; Digit2 == 0 ?

; YES PRINT A SPACE

; ; ; ; ;

1 2 3 Print DP 4

; pF ; includes RETURN

;********************************************************** ; ; Formatted display of BCD work area for Inductor ; L_disp movf call F_L1 MOVF ANDLW beq CALL call CALL call call goto R_sign,w DATS bcd+0,W 0x0F F_L2 PutNyb Swap1 DoDP Move1 Swap2 F_L2U ; Sign

; Print DP ; Print mH. includes RETURN

;-------------------------------------------------F_L2 swapf ANDLW beq CALL CALL call call call F_L2U movlw goto bcd+1,W 0x0F F_L3 PutNyb DoDP Move1 Swap2 Move2 Unit3-0x2100 pmsg ; Print DP

; mH ; includes RETURN

;-------------------------------------------------F_L3 MOVF ANDLW beq CALL call call CALL call goto bcd+1,W 0x0F F_L4 PutNyb Swap2 Move2 DoDP Swap3 F_L4U

; Print DP ; Print uH. includes RETURN

;-------------------------------------------------F_L4 SWAPF ANDLW bne MOVLW call goto NoB1_L call bcd+2,W 0x0F NoB1_L 0x20 DATS NoB2_L Swap2 ; 1 ; Digit1 == 0 ?

; YES PRINT A SPACE

NoB2_L call CALL call call F_L4U movlw goto

Move2 DoDP Swap3 Move3 Unit4-0x2100 pmsg

; ; ; ;

2 Print DP 3 4

; uH ; includes RETURN

;-------------------------------------------------; ; Common subroutine for formatted output ; DoDP Swap0 Move0 Swap1 Move1 Swap2 Move2 Swap3 Move3 MOVLW goto SWAPF goto MOVF goto SWAPF goto MOVF goto SWAPF goto MOVF goto SWAPF goto MOVF goto '.' DATS bcd+0,W PutNyb bcd+0,W PutNyb bcd+1,W PutNyb bcd+1,W PutNyb bcd+2,W PutNyb bcd+2,W PutNyb bcd+3,W PutNyb bcd+3,W PutNyb ; Print DP ; Return from DATS ; GET NEXT DIGIT ; DISPLAY IT ; GET OTHER BCD DIGIT

;******************************************************************** ; ; Stack operations ; ;******************************************************************** ;add ; subtract divide multiply ; ; ; call goto call goto call goto call goto FPA24 S_fix FPS24 S_fix FPD24 S_fix FPM24 S_fix

Fix stack after add, subtract, divide & multiply

; S_fix

AND Collect ALL Floating Point Errors in FPE iorwf FPE,f ; W may hold Error (0xff) ; C -> B

copy CARGB1,BARGB1 copy CARGB0,BARGB0 copy CEXP,BEXP return ; ; ; Push stack (duplicates TOS) BARGB1,CARGB1 BARGB0,CARGB0 BEXP,CEXP

S_push copy copy copy

; B -> C

copy AARGB1,BARGB1 copy AARGB0,BARGB0 copy AEXP,BEXP return ; ; Swap A and B

; A -> B

S_swap swap AARGB1,BARGB1 swap AARGB0,BARGB0 swap AEXP,BEXP return

; A <-> B

;******************************************************************** ; ; Calculate Unknown Capacitance OR inductance ; ; Output: 24 bit positive integer (scaled) ; right justified in AARGB0, AARGB1, AARGB2 ; also as BCD in bcd:bcd+1:bcd+2:bcd+3 ; ;******************************************************************** C_calc call call call goto divide Get_Ccal multiply PorM ; Times 10,000 ( = 1000.0pF) ; includes return

;-------------------------------------------------------------------L_calc call call call L_divF1 call call call call call ; ; ; multiply Get_Lcal multiply Get_F1 S_push multiply S_swap divide ; Precomputed 1/(Ccal*4*PI*PI) ; Divide by F1^2

Handle space or - in front of FP number

PorM

btfss goto

AARGB0,7 Pplus 0x2d PMdisp 0x20 R_sign AARGB0,7

; test sign ; minus ; plus ; save for later display ; make plus anyway

Pminus movlw goto Pplus movlw

PMdisp movwf bcf ; ; ;

Format as raw BCD string in bcd:bcd+1:bcd+2:bcd+3 call iorwf goto INT2424 FPE,f B2_BCD ; To INT in AARGB0 etc. ; W may hold Error (0xff) ; includes return

;******************************************************************** ; ; Calculate (F1/F3)^2-1, leave result on stack ; ;******************************************************************** F1_F3 call goto Get_F3 F1_F1

;******************************************************************** ; ; Calculate (F1/F2)^2-1, leave result on stack ; ;******************************************************************** F1_F2 F1_F1 call call call call call call call goto Get_F2 Get_F1 divide S_push multiply Get_One S_swap subtract

; F1/Fx ; (F1/Fx)^2 ; (F1/Fx)^2-1 ; includes return

;******************************************************************** ; Fetch assorted things used for the calculation ; of Unknown L and C ; ;******************************************************************** Get_Lcal call movlw movwf movlw movwf movlw goto Get_Ccal call S_push 0xAB AEXP 0x38 AARGB0 0x4D B1_2_stak S_push ; make room first ; ; ; ; ; 2.53303e+13 Create FP version of Precomputed 1/(Ccal*4*PI*PI) times any needed fiddle factor (1/100)

; make room first

B1_2_stak Get_One

movlw movwf movlw movwf movlw movwf return call clrf clrf clrf movlw goto

0x8c AEXP 0x1C AARGB0 0x40 AARGB1 S_push AEXP AARGB0 AARGB1 0x01 LSB2stak F1 W2stak F2 W2stak F3 W2stak

; ; ; ; ;

10,000 Create FP version of Precomputed Ccal times any needed fiddle factor

; make room first ; Create a binary 1

Get_F1 Get_F2 Get_F3 ;

movlw goto movlw goto movlw goto

; Includes stack push ; Includes stack push ; Includes stack push

;******************************************************************** ; Copy 16 bit number, pointed to by W, to stack ; and convert to FP (positive value only) ; via a 24 bit number in AARGB0,1,2 ;******************************************************************** W2stak movwf call clrf clrf movf movwf incf LSB2stak movf movwf FSR S_push AEXP AARGB0 INDF,W AARGB1 FSR,F INDF,W AARGB2 ; 24 bit int -> 24 bit FP ; W may hold Error (0xff) ; Big Byte first ; then little byte ; make room first

CALL FLO2424 iorwf FPE,f RETURN

;******************************************************************** INCLUDE <FP.TXT> ;******************************************************************** ; ; Text Strings (stored in data EEPROM) ;

ORG 0x2100 ovr Unit1 Unit2 Unit3 Unit4 Cintro Lintro Calibr de de de de de de de de END " " " " " " " " Over Range ",0 nF",0 pF",0 mH",0 uH",0 C = ",0 L = ",0 Calibrating ",0

You might also like