;-------------------------------------------------------------------------;
; A countdown timer for Psychoanalysis ;
; ORIGINAL CODE April '99 Stan Ockers (ockers@anl.gov) ;
; Re-written by Brendon Archibald April 2007 ;
; Optimized for battery operation ;
; Moddified for use in the 16F648A uP - Use internal OSC No XTAL required ;
; My mods mostly have ;* comments original code is just ; ;
; Modifications from original code include: ;
; 1\ Auto restart when reached zero. ;
; 2\ 0 Digit blanking on least significant digits. ;
; 3\ Improved alarm noise by stopping interupts. ;
; 4\ Combined Set and Select switch functions (long press for Set) ;
; Changed set routine, now start button increments digits and ;
; 5\ select button locks in digits. ;
; 6\ Add power off feature combined with Start switch (long press) ;
; 7\ Add 2 min Auto shutdown timer when not counting. ;
; 8\ Whist in power down uP sleeps till start button pressed ;
; 9\ Remove CD4511 from original design - Use retlw table for segments ;
; Counts down from 0-99 min and 1-59 sec giving an alarm at 0 ;
; Initial counts are held in data EEPROM ;
; and can be selected and set with one button ;
; ;
; *RAO-RA3 to bases of NPN transistors connect to cathode's of displays. ;
; **RB0-RB6 to 7segment display digits a, b, c, d, e, f & g. ;
; * RA6 to Decimal Point Anode, Cathode to ground. ;
; RB7 to start pushbutton used to start countdown and power off . ;
; RA4 is an output whilst counting (Active low Open Drain) ;
; RA5 with pull-up resistor goes to PB to select from 15 starting counts ;
; RA7 go's to piezo element via 100r resistor which gives an alarm. ;
;-------------------------------------------------------------------------;
list p=16f648A ; list directive to define processor
#include <p16F648A.inc> ; processor specific variable definitions
errorlevel -302 ; suppress message 302 from list file
__CONFIG _CP_OFF & _DATA_CP_OFF & _LVP_OFF & _BOREN_OFF & _MCLRE_OFF & _WDT_OFF & _PWRTE_ON & _INTOSC_OSC_NOCLKOUT ;* Config's for MPLAB
;-------------------------------------------------------------------------;
; Here we define our own personal registers and give them names ;
; *All moved to 16F6xx register locations* ;
;-------------------------------------------------------------------------;
SEC EQU H'20' ; this register holds the value of seconds
SEC10 EQU H'21' ; holds value of 10's of seconds
MIN EQU H'22' ; holds value of minutes
MIN10 EQU H'23' ; holds value of 10's of minutes
DIGCTR EQU H'24' ; 8 bit counter, only 2 lowest bits actually used
DIGIT EQU H'25' ; hold digit number to access table
INTCNT EQU H'26' ; counts # interrupts to determine when 1 sec up
FUDGE EQU H'27' ; allows slight adjustment every 7 interrupts
RUNFLG EQU H'28' ; bit 0 only, tells if countdown in progress
SECNT EQU H'29' ; used in counting 50, 20 msec delays for 1 sec
CNTMSEC EQU H'2A' ; used in timing of milliseconds
ALARM EQU H'2B' ; bit 0 used as flag for when to alarm, ALSO SETS ALARM LENGTH
DISPSET EQU H'2C' ;* bit 0 tells if in SETDISP and avoid bit blanking routine
NOISELP EQU H'2D' ;* USED FOR NOISE LOOP
BEEPS EQU H'2E' ;* USED FOR NUMBER OF BEEPS
AUTOFF EQU H'2F' ;* USED FOR AUTO OFF TIMER
BEEPDUR EQU H'30' ;* TEMP REG FOR BEEP DURATION
PORTA_TEMP EQU H'31' ;* temporarily holds value of PORTA (MASKED)
DPLATCH EQU H'32' ;* Holds latched value for DP
DPCNT EQU H'33'
W_TEMP EQU H'70' ; temporarily holds value of W
STATUS_TEMP EQU H'71' ; temporarily holds value of STATUS
OFFSET EQU H'72' ; hold offset of address in EEPROM
;-------------------------------------------------------------------------;
; Here we give names to some numbers to make their use more clear ;
;-------------------------------------------------------------------------;
#DEFINE START_PB D'7'
;#DEFINE SET_PB D'6' ;** Delete use of set button on RB6
#DEFINE SELECT_PB D'5'
#DEFINE DP D'6'
#DEFINE RA7 D'7'
#DEFINE OUTPUT D'4'
;#DEFINE RB5 D'5' ;** Not needed anymore
;-------------------------------------------------------------------------;
; We set the start of code to orginate at location zero ;
;-------------------------------------------------------------------------;
ORG 0
GOTO MAIN ; jump to the main routine
NOP
NOP
NOP
GOTO INTERRUPT ; interrupt routine
;-------------------------------------------------------------------------;
;* Lookup table for 7segment display - replaces CD/HEF4511 display driver ; ;
;-------------------------------------------------------------------------;
SEGMENT ADDWF PCL,f ; Bit table data for 7 segment digits
RETLW B'00111111' ; "0" _a_
RETLW B'00000110' ; "1" f| |b
RETLW B'01011011' ; "2" |_g_|
RETLW B'01001111' ; "3" e| |c
RETLW B'01100110' ; "4" |_d_|
RETLW B'01101101' ; "5"
RETLW B'01111101' ; "6" g to a
RETLW B'00000111' ; "7"
RETLW B'01111111' ; "8"
RETLW B'01101111' ; "9"
RETLW B'00000000' ; "10 = blank"
RETLW B'01011100' ; "11 = o"
RETLW B'01110001' ; "12 = F"
RETLW B'01101101' ; "13 = S"
RETLW B'01111001' ; "14 = E"
RETLW B'01110000' ; "15 = t"
;-------------------------------------------------------------------------;
; This table is used to get a bit pattern that will turn on a digit ;
; But only if next segment is not = 0 ie. O bit blanking ;
; Bit blanking not used if in SETDISP routine ie. DISPSET flag set ;
; I know this can be done a better way but it worked so... ;
;-------------------------------------------------------------------------;
BITPAT2 ADDWF PCL,f ;* get bit pattern for transistors - NO BIT BLANKING
RETLW H'01' ;* 0001
RETLW H'02' ;* 0010
RETLW H'04' ;* 0100
RETLW H'08' ;* 1000
BLANK1 MOVF MIN10,f ;* check MIN10 for zero
BTFSS STATUS,Z ;*
SHOWMIN RETLW H'04' ;* 0100
MOVF MIN,f ;* check MIN for zero
BTFSS STATUS,Z
GOTO SHOWMIN ;* NOT 0 SO SHOW BIT
GOTO BLANKDIG ;* MIN10 & MIN = 0 SO BLANK BIT
BLANK2 MOVF MIN10,f ;* check MIN10 for zero
BTFSS STATUS,Z
GOTO SHOWSEC10
MOVF MIN,f ;* check MIN for zero
BTFSS STATUS,Z
SHOWSEC10 RETLW H'02' ;* 0010
MOVF SEC10,f ;* check SEC10 for zero
BTFSS STATUS,Z
GOTO SHOWSEC10 ;* NOT 0 SO SHOW BIT
GOTO BLANKDIG ;* MIN10 & MIN & SEC10 = 0 SO BLANK BIT
BITPAT BTFSC DISPSET,0 ;* If in display set mode
GOTO BITPAT2 ;* then goto BITBAT2 otherwise continue
BITPAT1 ADDWF PCL,f ;* get bit pattern for tranys, 0 turns segment on
SHOWSEC RETLW H'01' ;* 0001 Seconds never blank
GOTO BLANK2 ;* SEC10 digit call - Blank if MIN & SEC10 = 0
GOTO BLANK1 ;* MIN10 digit call - Blank if MIN10 & MIN = 0
MOVF MIN10,f ;* check MIN10 for zero
BTFSS STATUS,Z ;* If MIN10 = 0 Blank MIN10 Segment
SHOWMIN10 RETLW H'08' ;* 1000
BLANKDIG RETLW H'00' ;* 0000 Blank DIGITS if 0
;-------------------------------------------------------------------------;
; Initialization routine sets up ports and timer ;
;-------------------------------------------------------------------------;
INIT CLRF PORTB ; initialize PORTB
CLRF PORTA ; initialize PORTA
MOVLW H'07' ;* 16F6XX Specific - Turn comparators off and
MOVWF CMCON ;* enable pins for I/O functions
BSF STATUS,RP0 ; Select Bank1
MOVLW B'10000000' ; RB7 input all others outputs
MOVWF TRISB ;* Updated command from original code
MOVLW B'00100000' ; Port RA5 input, others outputs
MOVWF TRISA ;* Updated command from original code
MOVLW H'03' ; prescaler on TMR0 and 1:16
MOVWF OPTION_REG ;* write to OPTION register * Updated command
BCF STATUS,RP0 ; back to bank0
MOVLW H'A0' ; GIE & T0IE set T0IF cleared
MOVWF INTCON
MOVLW H'F4' ; initialize INTCNT
MOVWF INTCNT
MOVLW H'06' ; initialize FUDGE
MOVWF FUDGE
CLRF OFFSET ; initialize OFFSET
MOVLW D'122' ;* initialize DPCNT
MOVWF DPCNT ;*
BSF PORTA,OUTPUT ;* Set OUTPUT RA4 (Counting not in Progress)
RETURN
;-------------------------------------------------------------------------;
; This is the interrupt routine that is jumped to when TMR0 overflows ;
;-------------------------------------------------------------------------;
INTERRUPT MOVWF W_TEMP ; save W
SWAPF STATUS,W ; save status
MOVWF STATUS_TEMP ; without changing flags
BCF STATUS,RP0 ; return to bank 0
BCF STATUS,RP1 ; return to bank 0 (shut ric up)
MOVF PORTA,W ;* Save PORTA to w reg
ANDLW B'11010000' ;* Mask off RA7,RA6 & RA4 (Outputs)
MOVWF PORTA_TEMP ;* Save it for later
MOVWF PORTA ;* Load it back into PORTA i.e. blank digits only
INCF DIGCTR,f ; next digit #
MOVF DIGCTR,W ; get it into W
ANDLW H'03' ; mask off 2 lowest bits
MOVWF DIGIT ; save it for later
ADDLW H'20' ;* point at register to display - moved due to 16F6XX
MOVWF FSR ; use as pointer
MOVF INDF,W ; get value of reg pointed to into W
CALL SEGMENT ;* Call segment lookup, return with value in w
MOVWF PORTB ; load w into portb - output to 7seg display's
MOVF DIGIT,W ; recall digit #
CALL BITPAT ;* get bit pattern, return with value in w
ADDWF PORTA_TEMP,W ;*Add bit pattern to PORTA_TEMP keep value in W
MOVWF PORTA ; load w into porta - i.e select segment/ETC
DECFSZ DPCNT,f ;* Decrement and check if DPCNT = 0
GOTO CONTINT ;* Not 0 so continue interrupt
COMF DPLATCH,F ;* Is 0 so invert DPLATCH
;MOVLW D'122' ;* Reset DPCNT
;MOVWF DPCNT ;*
CONTINT DECFSZ INTCNT,f ; finished 1 sec ?
GOTO RESTORE ; not yet, return and enable inter.
CALL EVERYSEC ; go to every second routine
MOVLW H'F4' ; reset INTCNT to normal value
MOVWF INTCNT
DECFSZ FUDGE,f ; time for fudge?
GOTO RESTORE ; not yet, continue on
MOVLW H'06' ; reset FUDGE to 6
MOVWF FUDGE
INCF INTCNT,f ; INTCNT to 245
RESTORE SWAPF STATUS_TEMP,W ; get original status back
MOVWF STATUS ; into status register
SWAPF W_TEMP,f ;* old no flags trick again
SWAPF W_TEMP,W ;* to restore W
BCF INTCON,T0IF ; clear the TMR0 interrupt flag
RETFIE ; finished
;-------------------------------------------------------------------------;
; This routine is called by the interrupt routine every second ;
;-------------------------------------------------------------------------;
EVERYSEC BTFSS RUNFLG,0 ; return if runflg not set
RETURN
BSF DPLATCH,0
MOVLW D'122' ;* Reset DPCNT
MOVWF DPCNT
DECF SEC,f ; decrement seconds digit
INCFSZ SEC,W ; test for underflow
GOTO CKZERO
MOVLW H'09'
MOVWF SEC ; reset sec to 9
DECF SEC10,f ; decrement SEC10
INCFSZ SEC10,W ; check underflow
GOTO CKZERO
MOVLW H'05'
MOVWF SEC10 ; reset SEC10 to 5
DECF MIN,f ; decrement MIN
INCFSZ MIN,W ; check underflow
GOTO CKZERO
MOVLW H'09'
MOVWF MIN ; reset MIN to 9
DECF MIN10,f ; decrement MIN10
CKZERO MOVF SEC,f ; test SEC for zero
BTFSS STATUS,Z
RETURN
MOVF SEC10,f ; check SEC10 for zero
BTFSS STATUS,Z
RETURN
MOVF MIN,f ; check MIN for zero
BTFSS STATUS,Z
RETURN
MOVF MIN10,f ; check MIN10 for zero
BTFSS STATUS,Z
RETURN
CLRF RUNFLG ; stop the countdown
BCF PORTA,DP ;* clear decimal point
BSF ALARM, 0 ; set the alarm flag
RETURN
;-------------------------------------------------------------------------;
; This routine is called by the MAINLOOP to set or clear the DP ;
;-------------------------------------------------------------------------;
DPSET BTFSC DPLATCH,0 ;* Test DPLATCH bit0
GOTO DPOFF ;* If 0 clear decimal point
BSF PORTA,DP ;* If 1 turn on decimal point
RETURN
DPOFF BCF PORTA,DP ;* TURN OFF decimal point
RETURN
;-------------------------------------------------------------------------;
; This is a routine to read a byte from the data EEPROM ;
;-------------------------------------------------------------------------;
READEE BSF STATUS,RP0 ;* change to bank 1 - needed it
MOVWF EEADR ; set up eeprom address from W
BSF EECON1,RD ; set the read bit
MOVF EEDATA,W ; return value in W
BCF STATUS,RP0 ;* back to bank 0
RETURN
;-------------------------------------------------------------------------;
; This routine fills the display registers from data EEPROM ;
;-------------------------------------------------------------------------;
GETEE MOVLW H'01' ; EEprom location 1 +
ADDWF OFFSET,W ; offset from start
CALL READEE ; into W
MOVWF SEC ; into SEC register
MOVLW H'02' ; location 2 +
ADDWF OFFSET,W ; offset from start
CALL READEE ; into W
MOVWF SEC10 ; into SEC10 register
MOVLW H'03' ; location 3 +
ADDWF OFFSET,W ; offset from start
CALL READEE ; into W
MOVWF MIN ; into MIN register
MOVLW H'04' ; location 4 +
ADDWF OFFSET,W ; offset from start
CALL READEE ; into W
MOVWF MIN10 ; into MIN10 register
RETURN
;-------------------------------------------------------------------------;
; This routine writes a byte to data EEPROM ;
;-------------------------------------------------------------------------;
WRITECHK BCF INTCON,GIE ; clear GIE, disable interrupts
WRITEEE BTFSC INTCON,GIE ;* Check if interrupt is disabled
GOTO WRITECHK ;* If not disabled then do so
BSF STATUS,RP0 ; Change to bank1
CLRF EECON1
BSF EECON1,WREN ; enable write
MOVLW H'55' ; magic sequence
MOVWF EECON2
MOVLW H'AA'
MOVWF EECON2
BSF EECON1,WR ;* Write data to EEPROM
EELOOP BTFSC EECON1,WR ; wait for WR to go low i.e. Finished write
GOTO EELOOP ; not yet check again
BCF EECON1,WREN ;* Finished write, disable write enable
BCF EECON1,EEIF ; clear the interrupt flag
BCF STATUS,RP0 ; return to bank0
BSF INTCON, GIE ; re-enable interrupts
RETURN
;-------------------------------------------------------------------------;
; This routine puts display registers into data EEPROM ;
;-------------------------------------------------------------------------;
PUTEE
MOVF SEC,W
BSF STATUS,RP0 ;* change to bank 1 to make it work
MOVWF EEDATA
MOVLW H'01' ; EEPROM location 1 +
ADDWF OFFSET,W ; offset from start
MOVWF EEADR
CALL WRITEEE ; put SEC digit into EEprom
MOVF SEC10,W
BSF STATUS,RP0 ;* change to bank 1 to make it work
MOVWF EEDATA
MOVLW H'02' ; EEPROM location 2 +
ADDWF OFFSET,W ; offset from start
MOVWF EEADR
CALL WRITEEE ; put SEC10 digit into EEprom
MOVF MIN,W
BSF STATUS,RP0 ;* change to bank 1 to make it work
MOVWF EEDATA
MOVLW H'03' ; EEPROM location 3 +
ADDWF OFFSET,W ; offset from start
MOVWF EEADR
CALL WRITEEE ; put MIN digit into EEprom
MOVF MIN10,W
BSF STATUS,RP0 ;* change to bank 1 to make it work
MOVWF EEDATA
MOVLW H'04' ; EEPROM location 4 +
ADDWF OFFSET,W ; offset from start
MOVWF EEADR
CALL WRITEEE ; put MIN10 digit into EEprom
RETURN
;-------------------------------------------------------------------------;
; This is the main routine, the program starts here ;
;-------------------------------------------------------------------------;
MAIN CALL INIT ; set up ports etc.
;-------------------------------------------------------------------------;
; We will return to this point when alarm is shut off. ;
;-------------------------------------------------------------------------;
EE2D CALL GETEE ; put eeprom in display regs.
BCF RUNFLG, 0 ; clear run flag so no countdown
BCF ALARM, 0 ; clear alarm flag
BCF DISPSET,0 ;* Initialise DISPSET flag (Enable Blanking)
CALL WAITSTARTUP ; wait till no switches pressed
CALL WAITSELECT
;-------------------------------------------------------------------------;
; This loop checks for either pushbutton and acts accordingly ;
; If however no switches are pressed for over a preset time call the ;
; SHUTOFF routine. ;
;-------------------------------------------------------------------------;
; Setup AUTOFF TIMEOUT with interrupt gives 2 min delay
KEYCHKLOOP MOVLW H'78' ;* 120 INTO AUTO OFF COUNTER
MOVWF AUTOFF ;* 120 X .8SEC = 96sec BEFORE AUTO OFF
MOVLW H'C8' ;* 200 INTO FIRST COUNTER
MOVWF SECNT ;* 200 X 4MSEC = .8SEC or so
AUTOFFLOOP MOVLW H'04' ;* 4MSEC DELAY
CALL NMSEC
BTFSS PORTB,START_PB ; check for start pressed
GOTO STARTLONG ;* yes, check for long press
BTFSS PORTA,SELECT_PB ; No, check select pushbutton pressed
GOTO SELLONG ;* yes, check for long press.
DECFSZ SECNT,f ;* no switches, decrement secnt, check for 0
GOTO AUTOFFLOOP ;* secnt not 0 so loop
DECFSZ AUTOFF,f ;* secnt is 0, decrement autoff, check for 0
GOTO AUTOFFLOOP ;* autoff not 0 so loop
GOTO SHUTOFF ;* autoff is 0 so GOTO SHUTOFF
;-------------------------------------------------------------------------;
; Long Start press routine - If short press then skip to STARTCNT if long ;
; then blank display, stop interrupts and SLEEP till start pressed again. ;
; Upon Start press restart interupts and goto EE2D i.e. LIKE POWER UP
;-------------------------------------------------------------------------;
STARTLONG MOVLW H'23' ;* 35 DELAYS
MOVWF SECNT ;* INTO SECNT REGISTER
STARTLOOP CALL DLY20 ;* CALL 20 MSEC DELAY
BTFSC PORTB,START_PB ;* Check, START BUTTON
GOTO STARTCNT ;* IF IT IS (i.e SHORT PRESS) START COUNT
DECFSZ SECNT,f ;* IF NOT DECREMENT SECNT AND CHECK IF IT REACHES ZERO
GOTO STARTLOOP ;* IF IT HASNT GO AND CHECK BUTTON AGAIN
CALL SHORTBEEP ;* Make a small noise
SHUTOFF MOVLW H'0A' ;* IF THE START BUTTON IS STILL DOWN AFTER 35 LOOPS
MOVWF MIN10 ;* Blank 10's of minutes,
MOVLW H'0B' ;* put a o in
MOVWF MIN ;* minutes
MOVLW H'0C' ;* Put an "F" in
MOVWF SEC10 ;* 10's of seconds
MOVWF SEC ;* and seconds
CALL WAITSTARTUP
MOVLW H'02' ;* NUMBER OF BEEPS
MOVWF BEEPS ;* LOAD 5 INTO BEEPS
MOVLW H'02' ;* duration of beeps
MOVWF BEEPDUR ;* ETC
CLRF PORTB
CALL BEEP ;* CALL BEEP
MOVLW D'250'
CALL NMSEC
BCF INTCON, GIE ;* COME BACK FROM BEEP - DISABLE INTERUPTS
CLRF PORTB
MOVLW B'00010000' ;* select transistors - i.e. ALL OFF
MOVWF PORTA ;*
MOVLW H'08' ;* Set INTCON RBIE - wake on PORTB
MOVWF INTCON ;* Also GIE & T0IE & T0IF cleared
CLRF TMR0 ;* and clear timer 0 - SOUNDED LIKE A GOOD IDEA?
SLEEP ;* Goto sleep, wait for button
NOP ;* Required delay?
;BCF INTCON, RBIF ;* DIDNT WORK AND DIDNT SEEM TO NEED IT??
CALL SHORTBEEP ;* Make a small noise
MOVLW H'A0' ;* WAKE UP - GIE & T0IE set T0IF cleared
MOVWF INTCON ;* i.e. restart interupts
GOTO EE2D ;* Reload last eeprom & wait for start etc
;-------------------------------------------------------------------------;
; If start key has been pressed then start countdown process, ;
; I initially released this code with only the setting of the ;
; run flag included. If you think about it you must also reset ;
; TMR0 to zero. TMR0 is free running and could have any value ;
; 0-255 when the button in pressed. Also INTCNT has to be ;
; initialized because the previous count could have been cancelled. ;
;-------------------------------------------------------------------------;
STARTCNT CALL SHORTBEEP ;* Make a small noise
CALL WAITSTARTUP ; wait for release of start key
SUBSTART MOVLW D'244' ; reset INTCNT
MOVWF INTCNT
CLRF DPLATCH ; reset DPLATCH
CLRF TMR0 ; and clear timer 0
BSF RUNFLG, 0 ; start the countdown
;BCF PORTA,OUTPUT ;* Clear OUTPUT RA4 (Counting in Progress)
;-------------------------------------------------------------------------;
; Once started just loop looking for cancel or reaching 0000 ;
;-------------------------------------------------------------------------;
MAINLOOP BTFSS PORTB,START_PB ; countdown in progress, check start
GOTO STOPCNT ; Yes, Stop count
CALL DPSET ;* No start switch, Set or clear decimal point
BTFSS ALARM, 0 ; Reached 0000 yet?
GOTO MAINLOOP ; no, ALARM = 0 continue looping
BCF INTCON, GIE ; yes, ALARM = 1 disable interrupts
BCF PORTA,DP ;* Clear decimal point
BSF PORTA,OUTPUT ;* Set OUTPUT RA4 (Counting not in Progress)
CALL SOUNDALARM ; CALL SOUNDALARM routine and come back
BSF INTCON, GIE ; RE-ENABLE interrupts
CALL GETEE ; put eeprom in display regs.
BCF ALARM, 0 ; clear alarm flag
GOTO SUBSTART ; ***Auto Restart triger point***
STOPCNT BCF PORTA,DP ;* Clear decimal point
;BSF PORTA,OUTPUT ;* Set OUTPUT RA4 (Counting not in Progress)
CALL SHORTBEEP ;* Make a small noise
GOTO EE2D
;-------------------------------------------------------------------------;
; This code sounds the alarm ;
; Produces 1 long 1KHz tone at end of time out - ;
;-------------------------------------------------------------------------;
SOUNDALARM MOVLW B'00111111' ;* LOAD a "0" ONTO SEGMENTS
MOVWF PORTB ;* Load into PORTB
MOVLW H'01' ;* NUMBER OF BEEPS
MOVWF BEEPS
MOVLW H'14' ; ? delays of ? msec = ?sec or so into BEEPDUR reg
MOVWF BEEPDUR
BEEP BCF INTCON, GIE ;* DISABLE INTERUPTS T0 CLEAN UP SOUND
BEEP2 MOVFW BEEPDUR ;* LOAD BEEPDUR INTO W
MOVWF ALARM ; LOAD W INTO ALARM REG - lazy and use ALARM reg for tone duration
NOISE MOVLW H'FF' ; 255 delays of 400 usec = 954usec or so
MOVWF NOISELP ; into NOISELP register
NOISELOOP MOVF PORTA,W
ANDLW B'11010000'
XORLW B'10000000' ;* TOGGLE PORTA RA7 (Buzzer)
MOVWF PORTA
MOVLW H'08' ; delay 8x10=80 microseconds (Freq of buzz)
CALL N10USEC
INCF DIGCTR,f ;* If RA7 is a 0 increment digit #
MOVF DIGCTR,W ;* get it into W
ANDLW H'03' ;* mask off 2 lowest bits
CALL BITPAT2 ;* get bit pattern for transistors
ADDWF PORTA,f ;* As a result gives basic multiplex display
DIGDIS DECFSZ NOISELP,f ; finished delay?
GOTO NOISELOOP ;* NO - DO IT AGAIN
DECFSZ ALARM,f ; Check alarm reg for 0, decrement if not
GOTO NOISE ;* and loop
MOVLW B'00010000' ;* select transistors - i.e. ALL OFF
MOVWF PORTA ;*
MOVLW H'C8' ;* DELAY BETWEEN BEEPS
CALL NMSEC ;*
DECFSZ BEEPS,f
GOTO BEEP2
STOPBEEP BSF INTCON, GIE ; RE-ENABLE interrupts
RETURN
SHORTBEEP MOVLW D'100' ; 100 delays of 80usec = 8msec or so
MOVWF NOISELP
BEEPLOOP MOVLW B'10000000' ;* XOR (TOGGLE) RA7
XORWF PORTA,1
MOVLW H'08' ; delay 8x10=80 microseconds (Freq of buzz)
CALL N10USEC
DECFSZ NOISELP,f ; finished delay?
GOTO BEEPLOOP ;* NO - DO IT AGAIN
BCF PORTA,RA7 ;* YES BEEP PROCESS FINISHED CLEAR SPEAKER PIN
RETURN ;* GO BACK
;-------------------------------------------------------------------------;
; Wait for release of start button ;
;-------------------------------------------------------------------------;
WAITSTARTUP BTFSS PORTB,START_PB ; wait for release
GOTO WAITSTARTUP ; not released yet
CALL DLY20 ; debounce release
BTFSS PORTB,START_PB ; 2nd check, make sure released
GOTO WAITSTARTUP ; keep checking
RETURN
;-------------------------------------------------------------------------;
; Wait for release of select button ;
;-------------------------------------------------------------------------;
WAITSELECT BTFSS PORTA,SELECT_PB ; wait for release
GOTO WAITSELECT ; not yet
CALL DLY20 ; debounce release
BTFSS PORTA,SELECT_PB ; 2nd check, make sure released
GOTO WAITSELECT ; keep checking
RETURN
;-------------------------------------------------------------------------;
; Routine to follow sets the countdown time digit by digit ;
;-------------------------------------------------------------------------;
SETDISP2 BSF DISPSET, 0 ;* set the DISPSET flag - Disable bitblanking
MOVLW H'0A' ; put 10 in
MOVWF MIN10 ; 10's of minutes
MOVLW D'13' ; put S in
MOVWF MIN ; minutes
MOVLW D'14' ; put E in
MOVWF SEC10 ; 10's of seconds
MOVLW D'15' ; put t in
MOVWF SEC ; seconds
CALL SHORTBEEP ;* Make a small noise
CALL WAITSELECT
MOVLW H'0A' ; put 10 in digits, (no display)
MOVWF MIN ; minutes
MOVWF SEC10 ; 10's of seconds
MOVWF SEC ; seconds
STARTMIN10 CLRF MIN10 ; 0 now in MIN10
CALL WAITSELECT ;*
WAIT1 BTFSS PORTB,START_PB ; set key pressed?
GOTO MOREMIN10 ;*
BTFSS PORTA,SELECT_PB ;*
GOTO SETMIN ; yes MIN10 now set
GOTO WAIT1
MOREMIN10 CALL SHORTBEEP ;* Make a small noise
CALL WAITSTARTUP ; wait for release of set key
INCF MIN10,f ; every increment 10's MIN
MOVLW H'0A' ; reached 10?
SUBWF MIN10,W
BTFSC STATUS,Z ; Z set if reached 10
GOTO STARTMIN10 ; start again with 0
GOTO WAIT1 ; Check buttons again
SETMIN CALL SHORTBEEP ;* Make a small noise
STARTMIN CLRF MIN ; 0 into MIN
CALL WAITSELECT
WAIT2 BTFSS PORTB,START_PB ;*
GOTO MOREMIN
BTFSS PORTA,SELECT_PB ;*
GOTO SETSEC10 ;* yes, finished with MIN
GOTO WAIT2 ; Check buttons again
MOREMIN CALL SHORTBEEP ;* Make a small noise
CALL WAITSTARTUP ;*
INCF MIN,f ; every second increment MIN
MOVLW H'0A' ; reached 10?
SUBWF MIN,W
BTFSC STATUS,Z ; Z set if reached 10
GOTO STARTMIN ; put zero in if Z set
GOTO WAIT2 ; Check buttons again
SETSEC10 CALL SHORTBEEP ;* Make a small noise
STARTSEC10 CLRF SEC10 ; 0 into SEC10
CALL WAITSELECT ;*
WAIT3 BTFSS PORTB,START_PB ;*
GOTO MORESEC10 ;* yes quit incrementing
BTFSS PORTA,SELECT_PB ;*
GOTO SETSEC
GOTO WAIT3 ; continue wait
MORESEC10 CALL SHORTBEEP ;* Make a small noise
CALL WAITSTARTUP ;*
INCF SEC10,f ; every second increment 10's SEC
MOVLW H'06' ; reached 6?
SUBWF SEC10,W
BTFSC STATUS,Z ; Z set if reached 6
GOTO STARTSEC10 ; put zero in if Z set
GOTO WAIT3 ; Check buttons again
SETSEC CALL SHORTBEEP ;* Make a small noise
STARTSEC CLRF SEC
CALL WAITSELECT
;-------------------------------------------------------------------------;
; Subroutine to avoid a set time of 0000 ;
;-------------------------------------------------------------------------;
MOVF MIN10,f ; check MIN10 for zero
BTFSS STATUS,Z
GOTO WAIT4 ; Zero SEC reg and continue increment
MOVF MIN,f ; check MIN for zero
BTFSS STATUS,Z
GOTO WAIT4 ; Zero SEC reg and continue increment
MOVF SEC10,f ; check SEC10 for zero
BTFSS STATUS,Z
GOTO WAIT4 ; Zero SEC reg and continue increment
INCF SEC,f ; Put 1 in SEC reg and continue increment
WAIT4 BTFSS PORTB,START_PB ;*
GOTO MORESEC ;* yes finished setting digits
BTFSS PORTA,SELECT_PB ;*
GOTO FINSET ;* yes finished setting digits
GOTO WAIT4 ; continue wait
MORESEC CALL SHORTBEEP ;* Make a small noise
CALL WAITSTARTUP ;*
INCF SEC,f ;* increment SEC
MOVLW H'0A' ; reached 10?
SUBWF SEC,W
BTFSC STATUS,Z ; Z set if reached 10
GOTO STARTSEC ; Return to STARTSEC and start again
GOTO WAIT4 ; Not 10 continue to increment
FINSET CALL SHORTBEEP ;* Make a small noise
MOVLW D'100'
CALL NMSEC
CALL SHORTBEEP ;* Make a small noise
CALL WAITSELECT ;*
CALL PUTEE ; put new digits into EEPROM
BCF DISPSET, 0 ;* CLEAR the DISPSET flag - Enable bitblanking
GOTO KEYCHKLOOP ; start checking buttons again
;-------------------------------------------------------------------------;
; Selects starting count by incrementing OFFSET ;
;-------------------------------------------------------------------------;
SELLONG MOVLW H'23' ;* 700msec delay
MOVWF SECNT ;*
SELLOOP CALL DLY20 ;*
BTFSC PORTA,SELECT_PB ;* wait for release
GOTO SETSELECT ;* is released - (short press)
DECFSZ SECNT,f ;* not released, decrement SECNT check if 0
GOTO SELLOOP ;* not 0 do it again
GOTO SETDISP2 ;* is 0 (long press)
SETSELECT CALL SHORTBEEP
MOVLW D'4' ; offset up 4
ADDWF OFFSET,F ; next offset position
MOVLW D'60' ; reached 16th yet?
SUBWF OFFSET,W ; will give zero if yes
BTFSC STATUS,Z ; skip if not 64
CLRF OFFSET ; reset position to zero
;MOVLW 0 ; EEPROM location (LEFT ALL THIS OUT)
;MOVWF EEADR ; set up address (BECAUSE IT DIDNT WORK)
;MOVF OFFSET,W ; offset # into W (AND I FIGURED, OFFSET)
;MOVWF EEDATA ; set up data (WASNT CHANGED AFTER POWER UP)
;BCF INTCON,GIE ; clear GIE, disable interrupts (AND IT WOULD WEAR)
;CALL WRITEEE ; save # in location 0 (OUT EEPROM, AS I)
;BSF INTCON,GIE ; re-enable interrupts (WAS HAPPY TO HAVE)
CALL GETEE ; get new start count into display (LAST SETTING)
CALL WAITSELECT ; make sure select switch is up (TO LEAVE IT OUT)
GOTO KEYCHKLOOP ; start checking buttons again
;-------------------------------------------------------------------------;
; The following are various delay routines based on instruction length. ;
; The instruction length is assumed to be 1 microsecond (4Mhz crystal). ;
;-------------------------------------------------------------------------;
DLY20 MOVLW D'20' ; delay for 20 milliseconds
;*** N millisecond delay routine ***
NMSEC MOVWF CNTMSEC ; delay for N (in W) milliseconds
MSECLOOP MOVLW D'248' ; load takes 1 microsec
CALL MICRO4 ; by itself CALL takes ...
; 2 + 247 X 4 + 3 + 2 = 995
NOP ; 1 more microsec
DECFSZ CNTMSEC,f ; 1 when skip not taken, else 2
GOTO MSECLOOP ; 2 here: total 1000 per msecloop
RETURN ; final time through takes 999 to here
; overhead in and out ignored
;*** 1 millisecond delay routine ***
ONEMSEC MOVLW D'249' ; 1 microsec for load W
; loops below take 248 X 4 + 3 = 995
MICRO4 ADDLW H'FF' ; subtract 1 from 'W'
BTFSS STATUS,Z ; skip when you reach zero
GOTO MICRO4 ; loops takes 4 microsec, 3 for last
RETURN ; takes 2 microsec
; call + load W + loops + return =
; 2 + 1 + 995 + 2 = 1000 microsec
;*** N 10 microsecond delay routine ***
N10USEC MOVWF CNTMSEC ;* delay for N (in W) milliseconds
USECLOOP MOVLW D'1' ;* load takes 1 microsec
CALL MICRO4 ;* by itself CALL takes ...
;* 1 + 4 + 3 + 2 = 10
DECFSZ CNTMSEC,f ;* 1 when skip not taken, else 2
GOTO USECLOOP ;* 2 here: total 10 per usecloop
RETURN ;* final time through takes 9 to here
;* overhead in and out ignored
;-------------------------------------------------------------------------;
; Here we set up the initial values of the digits in data EEPROM ;
;-------------------------------------------------------------------------;
ORG H'2100'
DE 0, 0, 0, 1, 0 ; 1st starting # (Should be 1 minute)
DE 0, 0, 2, 0 ; 2nd starting # (Should be 2 minutes)
DE 0, 0, 3, 0 ; 3rd starting # (Should be 3 minutes)
DE 0, 0, 4, 0 ; 4th starting # (Should be 4 minutes)
DE 0, 0, 5, 0 ; 5th starting # (Should be 5 minutes)
DE 0, 0, 6, 0 ; 6th starting # 6 min
DE 0, 0, 7, 0 ; 7th starting # 7 min
DE 0, 0, 8, 0 ; 8th starting # 8 min
DE 0, 0, 9, 0 ; 9th starting # 9 min
DE 0, 0, 0, 1 ; 10th starting # 10 min
DE 0, 0, 0, 2 ; 11th starting # 20 min
DE 0, 0, 0, 3 ; 12th starting # 30 min
DE 0, 0, 0, 4 ; 13th starting # 40 min
DE 0, 0, 0, 5 ; 14th starting # 50 min
DE 0, 0, 0, 6 ; 15th starting # 60 min
END
file: /Techref/microchip/cntdn/cntdwn_16F648no4511_V4.asm, 39KB, , updated: 2007/4/3 17:55, local time: 2024/11/17 13:48,
|
| ©2024 These pages are served without commercial sponsorship. (No popup ads, etc...).Bandwidth abuse increases hosting cost forcing sponsorship or shutdown. This server aggressively defends against automated copying for any reason including offline viewing, duplication, etc... Please respect this requirement and DO NOT RIP THIS SITE. Questions? <A HREF="http://linistepper.com/techref/microchip/cntdn/cntdwn_16F648no4511_V4.asm"> microchip cntdn cntdwn_16F648no4511_V4</A> |
Did you find what you needed?
|