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

📄 thermo.asm

📁 This is the simple digital thermometer asm source code.
💻 ASM
字号:
;----------------------------------------------------------------------------
; Date		: 2nd December 2003
; Project	: Led Thermometer
; Frequency	: 4 MHz
; Device used	: 16F877
; Oscillator	: XT
; Watchdog	: OFF    
; Copyright	:  
; Designed by	: Roy Thomas
; Comments	:
; Dowloaded from Downloads at HamRadioIndia ( www.hamradioindia.org )
;----------------------------------------------------------------------------
                LIST p=16F877

;----------------------------------------------------------------------------
w		equ 0    ; working reg:
f		equ 1    ; same reg: 
;----------------------------------------------------------------------------
; STATUS FLAGS
;----------------------------------------------------------------------------
carry		equ 0
zero		equ 2
rp0             equ 5  ; bank selection
rp1             equ 6
;----------------------------------------------------------------------------
; SFR's - SPECIAL FUNCTIONS REGISTERS
;----------------------------------------------------------------------------
indf		equ 00
tmr0		equ 01
optionreg       equ 01 ;bank 1
pcl		equ 02
status		equ 03
fsr		equ 04
trisa           equ 05h ; bank1
trisd           equ 08h ; bank1
trisb           equ 06h ; bank1
trise           equ 09  ; bank1
trisc           equ 07h ; bank 1       
porta		equ 05
portb		equ 06
portc		equ 07
portd           equ 08
porte           equ 09 
pclath		equ 0Ah      
intcon		equ 0Bh
tmr1l		equ 0Eh
tmr1h		equ 0Fh
pir1		equ 0Ch
pie1		equ 0Ch	; other bank
t1con		equ 10h
rcsta		equ 18h
txsta		equ 18h	; other bank
txreg		equ 19h
spbrg		equ 19h	; other bank
rcreg		equ 1Ah          
adresl		equ 1Eh ; Bank 1
adresh          equ 1Eh
adcon0		equ 1Fh
adcon1		equ 1Fh	; other bank
_WDT_OFF        equ 3FFBh
_XT_OSC         equ 3FFDh
;----------------------------------------------------------------------------
; GPR - GENERAL PURPOSE REGISTERS area
;----------------------------------------------------------------------------
                CBLOCK 20h
simage
wimage
digit1
digit2
digit3
ledindex
delaysmall
delaylarge
delaytime
resultlbyte
resulthbyte
tmrodelay
count   
temp    
H_byte   
L_byte   
Treultlbyte
Tresulthbyte
TH_byte
TL_byte
R0                ; RAM Assignments
R1       
R2       

                ENDC

;----------------------------------------------------------------------------
; Constants & Declarations
;----------------------------------------------------------------------------
gie		equ 7	; INTCON
go              equ 2   ; a/d conversion start/stop 
T0IF            equ 2   ; timer0 overfow check flag 
ADON            equ 0   ; switch on a/d converter. 
;----------------------------------------------------------------------------
; DEFINE
;----------------------------------------------------------------------------
;configuration bits
       __CONFIG        _XT_OSC & _WDT_OFF                      
;----------------------------------------------------------------------------
; RESET VECTOR
;----------------------------------------------------------------------------
                ORG 0
                goto   start
;  
;----------------------------------------------------------------------------
                org 04
isr		movwf   wimage      ; saving critical registers
		swapf   status,w
		movwf   simage
                movf    H_byte,w
                movwf   TH_byte     ; these are also modified during isr,
                movf    L_byte,w    ; so have to be saved till next cycle.
                movwf   TL_byte 
         
;----------------------------------------------------------------------------
;  IS routines goes here
;----------------------------------------------------------------------------
                decfsz     tmrodelay,f   ; wait for 16 interrupts to pass
                goto       isrexit
                nop
                call       atodcon       ; on 16th interrupt,conversion. 
                call       atodforbcd
                movlw      .16
                movwf      tmrodelay     ; reinitialise the variable

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

isrexit         nop                       ; seems to be a timing violation
                nop                       ; so just a delay! 
                bcf     intcon,T0IF
        	bsf     intcon,gie
                movf    TH_byte,w
                movwf   H_byte
                movf    TL_byte,w         ;   replace the registers,
                movwf   L_byte            ;   clear the tmr0 flag caused 
                bcf     intcon,T0IF       ;   the interrupt. 
        	swapf   simage,w
 		movwf   status
        	swapf   wimage,f
                swapf   wimage,w  
	        
		retfie
;End of interrupt service routines
;----------------------------------------------------------------------------

display_table 
	     addwf      pcl,f      ; W + PCL -> PCL
             retlw      b'00111111' ;  '0'
             retlw      b'00000110' ;  '1'
             retlw      b'01011011' ;  '2'
             retlw      b'01001111' ;  '3'
             retlw      b'01100110' ;  '4'   table for segment patterns
             retlw      b'01101101' ;  '5'
             retlw      b'01111101' ;  '6'
             retlw      b'00000111' ;  '7'
             retlw      b'01111111' ;  '8'
             retlw      b'01100111' ;  '9'
             retlw      b'10000000' ;  '.'

;----------------------------------------------------------------------------
; SUBROIUTINES
;----------------------------------------------------------------------------

display   
           movlw     b'00000001'   ;  select the left most digit
           movwf     ledindex      ;
	   movwf     porte         ;  digit selecting transistor on!
           movf      digit1,w      ;  get the bcd value to display
           call      digitout      ;  illuminate for a period
         
           rlf       ledindex,f    ;  rotate to left to select next digit  
           movf      ledindex,w    ;  enable next digit
           movwf     porte         ;  digit selecting transistor on!
           movf      digit2,w      ;  get the bcd value.
           call      digitout      ;  illuminate for a period   
           
           rlf       ledindex,f
           movf      ledindex,w    ;  last digit selected.
           movwf     porte 
           movf      digit3,w      ;  get bcd value
           call      digitout      ;  illuminate for a period
           return
;----------------------------------------------------------------------------

digitdelay movlw     5h             ;  outer loop for delay
           movwf     delaylarge
loopl      decf      delaylarge,f 
           btfsc     status,zero
           return
           movlw     0FFh
           movwf     delaysmall
loops      decfsz    delaysmall,f   ;  inner loop for delay
           goto      loops
           goto      loopl             

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

digitout   nop
           call       display_table ; illuminate digit and wait 
           movwf      portd         ; for some time
           call       digitdelay
           clrf       portd         ; off the digit and return.
           clrf       porte
           return 	 
;----------------------------------------------------------------------------

iniports   bsf       status,rp0
           movlw     b'00000001'     ;  input for analogue  temp sensor
           movwf     trisa           ;  RA0 as the input 
           clrw
           movwf     trisd           ;  all portd output for segments.
           movwf     trise           ;  porte for digit selection
           bcf       status,rp0      ;  return to bank 0 and return  
           clrf      porta
           clrf      portd
           clrf      porte
           return
;----------------------------------------------------------------------------

iniatod    bsf      status,rp0
           movlw    b'10001110'      ;  result right justified ,ra0 as
           movwf    adcon1           ;  analogue input with Vdd as Vref
           bcf      status,rp0           
	   movlw    b'01000000'      ;  a/d clock Tosc*8 and Ra0 channel
           movwf    adcon0           ;  selected. a/d module still off.
           return 
;----------------------------------------------------------------------------

initimer  bsf       status,rp0       ;  bank 1
          movlw     b'10000111'      ;  timer0 on internal clock pulse
          movwf     optionreg        ;  prescaler 1:256
          movlw     b'10100000'      ;  gie and TMR0 interrupt enabled  
          movwf     intcon           ;  all ready! 
	  bcf       status,rp0
          movlw     .1
          movwf     tmrodelay        ; initialise the delay variable to     
          return                     ; start conversion on 1st interrupt
;----------------------------------------------------------------------------

atodcon    bsf       adcon0,ADON ; swich on a/d converter.
           movlw     0Ah
           movwf     delaytime
aquiloop   decfsz    delaytime,f ; wait for aqusition time. 
           goto      aquiloop
           bsf       adcon0,go   ; conversion starts now!
converloop btfsc     adcon0,go   ; loop until conversion complete.
           goto      converloop
           bsf       status,rp0  ;  bank for adresl 
           movf      adresl,w    ;  low byte of result.
           bcf       status,rp0
           movwf     resultlbyte ;  a/d low byte saved
           movf      adresh,w    ;  high byte of result
           movwf     resulthbyte ;  a/d high byte saved    
           return
;----------------------------------------------------------------------------

B2_BCD  bcf     status,0                ; clear the carry bit
	movlw   .16
	movwf   count
	clrf    R0
	clrf    R1
	clrf    R2
loop16  rlf     L_byte, f
	rlf     H_byte, f
	rlf     R2, f
	rlf     R1, f
	rlf     R0, f
;
	decfsz  count, f                ; routine for bcd conversion
	goto    adjDEC
	retlw  0
;
adjDEC  movlw   R2
	movwf   fsr
	call    adjBCD                    ; no bank switching, always 
;                                         ; indirect access for RAM
	movlw   R1
	movwf   fsr
	call    adjBCD
;
	movlw   R0
	movwf   fsr
	call    adjBCD
;
	goto    loop16
;
adjBCD  movlw   3
	addwf   0,W
	movwf   temp
	btfsc   temp,3          ; test if result > 7
	movwf   indf
	movlw   30
	addwf   0,W
	movwf   temp
	btfsc   temp,7          ; test if result > 7
	movwf   indf               ; save as MSD
	retlw   0
;---------------------------------------------------------------------------- 
;   Arrange the  result as digits 1,2,3.

bcdsplit   movf     R1,w     ;   bring first nibble  
           andlw    0Fh      ;   mask the upper nibble
           movwf    digit1   ;   send to display routine variable.

           movf     R2,w     ;   bring the second digit!
           andlw    0F0h     ;   mask the lower nibble.
           movwf    digit2   ;   send to display routine variable.
           swapf    digit2,f ;   after swaping!
 
           movf     R2,w     ;   Again bring the lowbyte
           andlw    0Fh      ;   mask the upper nibble
           movwf    digit3   ;   send it to display routine variable     
           return
;----------------------------------------------------------------------------
atodforbcd  rrf      resultlbyte,f  ; routine for dividing the value 
            bcf      status,carry
            rrf      resulthbyte,f            
            btfsc    status,carry
            bsf      resultlbyte,7  ;
xxx         movf     resultlbyte,w  ; 
            movwf    L_byte         ; bcd conversion subroutine.   
            movf     resulthbyte,w  ;
            movwf    H_byte         ; 
            return
;----------------------------------------------------------------------------
; Main program starts
;----------------------------------------------------------------------------
start	 clrf   simage
         clrf   wimage
         clrf   digit1
         clrf   digit2
         clrf   digit3
         clrf   ledindex
         clrf   delaysmall
         clrf   delaylarge 
         clrf   porta
         clrf   portd
         clrf   porte
         bsf    status,rp0
         clrf   trisd
         clrf   trisb
         clrf   trisc
	   clrf   trise
         clrf   trisa
         bcf    status,rp0
         bcf    status,rp1
         call   iniports    ;  initialise all relevent ports.
         call   iniatod     ;  initialise a/d converter module.       
         call   initimer    ;  initialise timer0 so to derive a time base.
          
;-------------------------------------------
main       ;call     atodcon         ;   conversion and result saved.
           ;call     atodforbcd      ;   result moved for bcd conversion
           call     xxx
           call     B2_BCD         ;   bcd conversion
           call     bcdsplit       ;   seperate nibbles for digits
           call     display        ;   display the digits.  
	
           goto main


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


	        END
;-------------------------------------------

⌨️ 快捷键说明

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