;Philip Weiss
;Joel Avrunin


.nolist				;Suppress listing of include file
.include "8535def.inc"		;Define chip particulars.list
;***** register variables
.def	save		=r1		;saves the SREG in ISRs
.def	reload	=r2		;timer 0 interval
.def	lcdstat	=r3		;used with the lcd display setup
.def	maybe		=r4		;used in the button debounce routine
.def	savSREG	=r5		;saves the SREG in an interrupt
.def	thirtyms 	=r6		;thirty millisecond counter
.def	butflag	=r7		;=1 if button was pressed
.def	leap		=r8		;used to check for a leap year
.def	a1on		=r9		;=1 if the alarm is set to turn on
.def	ahour		=r10		;hour the alarm will turn on
.def	amin		=r11		;minute the alarm will turn on
.def	secflash	=r12		;used to blink the green LED every second
.def	timetemp 	=r14		;temporary register used when outputting time
.def	asciitemp	=r15		;temporary register used when outputting the date
.def	temp		=r16		;General use temp register
.def	timeout	=r17		;Timeout value in mSec passed to subroutine
.def	charcnt	=r18		;Char position on the display
.def	seconds	=r20		;seconds on the clock
.def	minutes	=r21		;minutes on the clock
.def 	hours		=r22		;hours on the clock
.def	month		=r23		;current month
.def	date		=r24		;current date
.def	year		=r25		;current year
.def  key     	=r26		;used in debounce routine
.def  press   	=r27		;button pressed out of debounce routine
.def	state		=r28		;current state in debounce routine
.def	temp2		=r30		;another temp
;***** Other equates
.equ	lcdrs		=PD6		;LCD rs pin connected to PD6
.equ	lcdrw		=PD5		;LCD r/w pin connected to PD5
.equ	lcde		=PD4		;LCD e pin connected to PD4
.equ	down		=0b11100111 ; * (time down)
.equ	up		=0b11101101 ; # (time up)
.equ	set		=0b11101110 ; D (set)
.equ	almset	=0b11011110 ; C (set alarm)
.equ	toga1		=0b01111110 ; A	(turn on/off alarm)

.cseg

;	Interrupt vectors

.org $0000
	rjmp 	RESET	;reset entry vector
	reti		
	reti
	reti
	rjmp	timer2	;used for the real-time clock
	reti
	reti
	reti
	reti
	rjmp	timer0	;interrupts every 1 millisecond
	reti
	reti	
	reti	
	reti
	reti
	reti
	reti

keytbl: .db 0b11101110, 0b11101101, 0b11101011, 0b11100111
       .db 0b11011110, 0b11011101, 0b11011011, 0b11010111
       .db 0b10111110, 0b10111101, 0b10111011, 0b10110111
       .db 0b01111110, 0b01111101, 0b01111011, 0b01110111

sethourd:	.db	"------", 0x00, 0x00
setmind:	.db		"----", 0x00, 0x00
setalarm:	.db	"----", 0x00
setdate:	.db	"------", 0x00, 0x00

;	Main program entry point on reset
RESET:  
	ldi	temp, LOW(RAMEND) ;setup stack pointer
	out 	SPL, temp
	ldi	temp, HIGH(RAMEND)
	out	SPH, temp

	ldi	temp,0
	out 	TIMSK,temp

      ldi     Temp, 3         ;prescale timer0 by 64
      out     TCCR0, Temp
      ldi     temp,256-62   ;reload timer since
      out     TCNT0, temp   ;62.5 x (64x.25) microSec = 1.0 mSec.

	;set up pin0(alarm buzzer) and pin1(blinking led) on portc to be an output
	ldi	temp,3
	out	DDRC,temp

	;set up timer2
	ldi	temp,0b00001000	;run asynchronously from cpu clock
	out	ASSR,temp
	clr	temp
	out 	TCNT2,temp
	ldi	temp,0b00000101	;prescale by 128 to overflow every 1 second
	out	TCCR2,temp

waitlp:	;wait until TC2 is updated
	in	temp,ASSR
	andi	temp, 0x07
	cpi	temp,0x07
	breq	waitlp

	ldi	temp,0b01000001	;enable timer2 and timer0 overflow interrupt
	out 	TIMSK,temp


	;set up port B
        ser     Temp            ;set PORTB to be
        out     DDRB,Temp       ;all outputs


	sei		;Enable interrupts

	ldi	timeout,255	;Wait 255 mSec to let the 32.768KHz crystal settle
	rcall	delay
	
	clr	temp
	mov	thirtyms,temp
	mov	butflag,temp
	;initialize system on reset
	rcall   lcdinit	;initialize the lcd
        rcall   lcdclr	;clear the lcd
        clr     charcnt
	ldi	state,1
	clr	hours
	clr	minutes
	clr	seconds
	clr	temp
	mov	a1on,temp
	mov	secflash,temp
	mov	ahour,temp
	mov	amin,temp
	ldi	month,1
	ldi	date,1
	ldi	year,0
isettime:	;display the set hour string
	rcall	lcdclr
	clr     charcnt
        ldi     ZH, HIGH(sethourd<<1)
        ldi     ZL, LOW(sethourd<<1)

nextc:  lpm     ;r0             ;Get next character from flash
       	tst     r0              ;See if at end of message
       	breq    end1            ;If so, next message
       	cpi     charcnt,8       ;addressing changes at char #8!
       	brne    wrtit           ;at char 8, fix the addressing
       	ldi     temp,0xC0       ;Set address to last 8 chars

	rcall   lcdcmd

wrtit:  mov     temp,r0         ;Send it to the LCD
      	rcall   lcdput
       	adiw    ZL,1            ;Increment Z-pointer
       	inc     charcnt         ;keep track of chars on display
       	rjmp    nextc           ;Loop for more
end1:  	clr     charcnt

	ldi	temp,1
	mov	butflag,temp
sethour:
	ldi	temp,0
	cp	butflag,temp	
	breq	nopress4	;see if button was pressed
	ldi	temp, 29
	cp	temp, thirtyms
	brne	sethour
	rcall	disptime	;updates time on clock (called evert 30 msec)
	rcall	debounce	;check for a button press
	cpi	state, 1	;if the state != 1 go back to sethour
	brne	sethour
nopress4:
	ldi	temp,0
	mov	butflag,temp	;clear butflag
	ldi	temp,29
	cp      temp,thirtyms
        brne    d1
	rcall	disptime
        rcall   debounce
d1:	cpi	press,up	;see if up key was pressed
        brne	next0
	ldi	temp,1
	mov	butflag,temp	;set butflag since key was pressed
	inc	hours		
	cpi	hours,24	;hours should not equal 24
	breq	zhour		
	rjmp  	sethour		;go to top and wait for another button
zhour:	ldi	hours,0		;reset hours to zero if incremented past 23
	rjmp	sethour		;go to top and wait for another button
next0:	cpi	press,down	;see if down key was pressed
	brne	next1
	ldi	temp,1
	mov	butflag,temp	;set butflag since key was pressed
	dec	hours
	cpi	hours,255	;see if hours was decremented too much
	breq	mhour
	rjmp	sethour		;go to top and wait for another button
mhour:	ldi	hours,23	;set hours to 23 if decremented below 0
	rjmp	sethour		;go to top and wait for another button
	ldi	hours,0
next1:	cpi	press,set	
	breq	iisetmin	;if the set button was pressed set the minutes
	brne	sethour

iisetmin:	;display the set minutes prompt				
	rcall	lcdclr
	clr     charcnt
        ldi     ZH, HIGH(setmind<<1)
        ldi     ZL, LOW(setmind<<1)

mnextc:  lpm     ;r0             ;Get next character from flash
       	tst     r0              ;See if at end of message
       	breq    mend1            ;If so, next message
       	cpi     charcnt,8       ;addressing changes at char #8!
       	brne    mwrtit           ;at char 8, fix the addressing
       	ldi     temp,0xC0       ;Set address to last 8 chars

	rcall   lcdcmd

mwrtit:  mov     temp,r0         ;Send it to the LCD
      	rcall   lcdput
       	adiw    ZL,1            ;Increment Z-pointer
       	inc     charcnt         ;keep track of chars on display
       	rjmp    mnextc           ;Loop for more
mend1:  	clr     charcnt
	ldi	temp,1
	mov	butflag, temp
isetmin:
	ldi	temp,1
	mov	butflag,temp

setmin:	
	ldi	temp,0
	cp	butflag,temp
	breq	nopress5
	ldi	temp, 29
	cp	temp, thirtyms
	brne	setmin
	rcall	disptime
	rcall	debounce
	cpi	state, 1
	brne	setmin
nopress5:
	ldi	temp,0
	mov	butflag,temp
	ldi	temp,29
	cp      temp,thirtyms
        brne    d2
	rcall	disptime
        rcall   debounce
d2:	cpi	press,up
        brne	next2
	ldi	temp,1
	mov	butflag,temp
	inc	minutes
	cpi	minutes,60	;minutes should not equal 60
	breq	zmin
	rjmp  	setmin
zmin:	ldi	minutes,0	;reset to zero if incremented past 59
	rjmp	setmin
next2:	cpi	press,down
	brne	next3
	ldi	temp,1
	mov	butflag,temp
	dec	minutes
	cpi	minutes,255	
	breq	mmin
	rjmp	setmin
mmin:	ldi	minutes,59	;set to 59 if decremented below zero
	rjmp	setmin
	ldi	minutes,0
next3:	cpi	press,set	;if pressed, the time set is complete
	breq	timedone
	brne	setmin

timedone:	;display the set date prompt
	rcall	lcdclr
	clr     charcnt
        ldi     ZH, HIGH(setdate<<1)
        ldi     ZL, LOW(setdate<<1)

nextc2:  lpm     ;r0             ;Get next character from flash
       	tst     r0              ;See if at end of message
       	breq    end2            ;If so, next message
       	cpi     charcnt,8       ;addressing changes at char #8!
       	brne    wrtit2           ;at char 8, fix the addressing
       	ldi     temp,0xC0       ;Set address to last 8 chars

	rcall   lcdcmd

wrtit2:  mov     temp,r0         ;Send it to the LCD
      	rcall   lcdput
       	adiw    ZL,1            ;Increment Z-pointer
       	inc     charcnt         ;keep track of chars on display
       	rjmp    nextc2           ;Loop for more
end2:  	clr     charcnt


isetmonth:
	ldi	temp,1
	mov	butflag, temp
setmonth:
	ldi	temp,0
	cp	butflag,temp
	breq	nopress1
	ldi	temp, 29
	cp	temp, thirtyms
	brne	setmonth
	rcall	disptime
	rcall	debounce
	cpi	state, 1
	brne	setmonth
nopress1:
	ldi	temp,0
	mov	butflag,temp
	ldi	temp,29
	cp      temp,thirtyms
        brne    d3
	rcall	disptime
        rcall   debounce
d3:	cpi	press,up
        brne	next4
	ldi	temp,1
	mov	butflag,temp
	inc	month
	cpi	month,13	;month should not equal 13
	breq	zmonth
	rcall	asciidate	;show the date display
	rjmp  	setmonth
zmonth:	ldi	month,1		;reset months to 1 if incremented past 12
	rcall	asciidate	;update the date display
	rjmp	setmonth
next4:	cpi	press,down
	brne	next5
	ldi	temp,1
	mov	butflag,temp
	dec	month
	cpi	month,0		;month should not equal zero
	breq	mmonth
	rcall	asciidate
	rjmp	setmonth
mmonth:	ldi	month,12	;set month to 12 if decremented below 1
	rcall	asciidate		;update the date display
	rjmp	setmonth
	ldi	month,1
next5:	cpi	press,set
	breq	isetday		;done with months, so set the date
	brne	setmonth

isetday:
	ldi	temp, 1
	mov	butflag, temp
	rcall	asciidate
setday:
	ldi	temp,0
	cp	butflag,temp
	breq	nopress2
	ldi	temp, 29
	cp	temp, thirtyms
	brne	setday
	rcall	disptime
	rcall	debounce
	cpi	state, 1
	brne	setday
nopress2:
	ldi	temp,0
	mov	butflag,temp
	ldi	temp,29
	cp      temp,thirtyms
        brne    d4
	rcall	disptime
        rcall   debounce
d4:	cpi	press,up
        brne	next6
	ldi	temp,1
	mov	butflag,temp
	inc	date
	cpi	date,32		;no months have 32 days
	breq	zday
	cpi	date,31		;if months incremented to 31 check if month
					;has 31 days to see if it is valid
	brne	ck29
	cpi	month,4
	breq	zday
	cpi	month,6
	breq	zday
	cpi	month,9
	breq	zday
	cpi	month,11
	breq	zday
ck29:	cpi	date,29		;needed to check February
	brne	norst
	cpi	month,2
	breq	zday
norst:	rcall	asciidate
	rjmp  	setday
zday:	ldi	date,1		;set the day to 1 if incremented past max day
	rcall	asciidate
	rjmp	setday
next6:	cpi	press,down
	brne	next7
	ldi	temp,1
	mov	butflag,temp
	dec	date
	cpi	date,0
	breq	mday
	rcall	asciidate
	rjmp	setday
mday:	cpi	month,4		;if decremented below one set to max day 
					;for given month
	breq	ld30
	cpi	month,6
	breq	ld30
	cpi	month,9
	breq	ld30
	cpi	month,11
	breq	ld30
	cpi	month,2
	brne	ld31
	ldi	date,28
	rjmp	dayp
ld31:	ldi	date,31
	rjmp	dayp	
ld30:	ldi	date,30
dayp:	rcall	asciidate
	rjmp	setday
	ldi	date,1
next7:	cpi	press,set
	breq	isetyear		;go to setting the year
	rjmp	setday
isetyear:
	ldi	temp,1
	mov	butflag, temp
setyear:
	ldi	temp,0
	cp	butflag,temp
	breq	nopress3
	ldi	temp, 29
	cp	temp, thirtyms
	brne	setyear
	rcall	disptime
	rcall	debounce
	cpi	state, 1
	brne	setyear
nopress3:
	ldi	temp,0
	mov	butflag,temp
	ldi	temp,29
	cp      temp,thirtyms
        brne    d5
	rcall	disptime
        rcall   debounce
d5:	cpi	press,up
        brne	next8
	ldi	temp,1
	mov	butflag,temp
	inc	year
	cpi	year,100		;year can't be 100 since only hold last two digits
	breq	zyear
	rcall	asciidate
	rjmp  	setyear
zyear:	ldi	year,0	;reset year to zero if incremented past 99
	rcall	asciidate
	rjmp	setyear
next8:	cpi	press,down
	brne	next9
	ldi	temp,1
	mov	butflag,temp
	dec	year
	cpi	year,255		;check if year was decremented below zero
	breq	myear
	rcall	asciidate
	rjmp	setyear
myear:	ldi	year,99	;set year to 99 if decremented below zero
	rcall	asciidate
	rjmp	setyear
	ldi	year,0
next9:	cpi	press,set
	breq	setdone		;if set was pressed, jump to main program loop
	rjmp	setyear
	
setdone:
	rcall	asciidate		;print the date
	ldi	temp, 1
	mov	butflag, temp
setdone1:
	ldi	temp,0
	cp	butflag,temp
	breq	nopress6
	ldi	temp, 29
	cp	temp, thirtyms
	brne	setdone1
	rcall	disptime		;display the time
	rcall	debounce		;run debounce routing
	cpi	state, 1
	brne	setdone1
nopress6:
	ldi	temp,0
	mov	butflag,temp
	ldi	temp,29
	cp      temp,thirtyms
      brne    d6
	rcall	asciidate
	rcall	disptime
      rcall   debounce
d6:	cpi	press,set
	brne	noset
	rjmp	isettime 		;if set was pressed, set the clock again
noset:	cpi	press,almset	;see if the alarm set button was pressed
	brne	noalmset
	rcall	alm1set		;set the alarm
noalmset:
	cpi	press,toga1		;check if the alarm on/off button was pressed
	brne	endpgm
	ldi	temp,1
	eor	a1on, temp		;turn the alarm on/off
	mov	butflag,temp
endpgm:	
	rjmp	setdone1		;back to top of main loop
;***********************************
lcdclr:
       ldi     temp,1          ;Clear LCD command
       rcall   lcdcmd
        ldi     temp,3
       mov     timeout,temp       ;Delay 3 mS for clear command
       rcall   delay
       ret
;================================================
;       Initialize LCD module
lcdinit:
       ;cbi     PORTB,0         ;Turn on LED 0
       ldi     temp,0          ;Setup port pins
       out     PORTD,temp      ;Pull all pins low
       ldi     temp,0xff       ;All pins are outputs
       out     DDRD,temp
       ldi     temp,15
       mov     timeout,temp      ;Wait at least 15 mS at power up
       rcall   delay

;     LCD specs call for 3 repetitions as follows:
       ;first rep

       ldi     temp,3          ;Function set
       out     PORTD,temp      ;to 8-bit mode
       nop                     ;nop is data setup time
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       ldi     temp,15
       mov     timeout,temp      ;Wait at least 15 mS
       rcall   delay
       ;second rep
       ldi     temp,3          ;Function set
       out     PORTD,temp
       nop
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       ldi     temp,15
       mov     timeout,temp      ;Wait at least 15 ms
       rcall   delay
       ;third rep
       ldi     temp,3          ;Function set
       out     PORTD,temp
       nop
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       ldi     temp,15
       mov     timeout,temp      ;Wait at least 15 ms
       rcall   delay
       ;Now change to 4-wire interface mode
       ldi     temp,2          ;Function set, 4 wire databus
       out     PORTD,temp
       nop
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
;       Finally, at this point,
;       the normal 4 wire command routine (lcdcmd) can be used
       ldi     temp,0b00100000 ;Function set, 4 wire, 1 line, 5x7 font
       rcall   lcdcmd
       ldi     temp,0b00001100 ;Display on, no cursor, no blink
       rcall   lcdcmd
       ldi     temp,0b00000110 ;Address increment, no scrolling
       rcall   lcdcmd
       ;sbi     PORTB,0         ;Turn off LED 0
       ret
;============================================
;       Wait for LCD to go unbusy
lcdwait:
       ;cbi     PORTB,1         ;Turn on LED 1
       ldi     temp,0xF0       ;Make 4 data lines inputs
       out     DDRD,temp
       sbi     PORTD,lcdrw     ;Set r/w pin to read
       cbi     PORTD,lcdrs     ;Set register select to command
waitloop:
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       in      lcdstat,PIND    ;Read busy flag
       ;Read, and ignore lower nibble
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       sbrc    lcdstat,3       ;Loop until done
       rjmp    waitloop
       ;sbi     PORTB,1         ;Turn off LED 1
       ret
;=============================================
;       Send command in temp to LCD
lcdcmd:
       push    temp            ;Save character
       rcall   lcdwait
       ldi     temp,0xFF       ;Make all port D pins outputs
       out     DDRD,temp
       pop     temp            ;Get character back
       push    temp            ;Save another copy
       swap    temp            ;Get upper nibble
       andi    temp,0x0F       ;Strip off upper bits
       out     PORTD,temp      ;Put on port
       nop                     ;wait for data setup time
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       pop     temp            ;Recall character
       andi    temp,0x0F       ;Strip off upper bits
       out     PORTD,temp      ;Put on port
       nop
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       ret
;=============================================
;       Send character data in temp to LCD
lcdput:
       push    temp            ;Save character
       rcall   lcdwait
       ldi     temp,0xFF       ;Make all port D pins outputs
       out     DDRD,temp
       pop     temp            ;Get character back
       push    temp            ;Save another copy
       swap    temp            ;Get upper nibble
       andi    temp,0x0F       ;Strip off upper bits
       out     PORTD,temp      ;Put on port
       sbi     PORTD,lcdrs     ;Register select set for data
       nop
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       pop     temp            ;Recall character
       andi    temp,0x0F       ;Strip off upper bits
       out     PORTD,temp      ;Put on port
       sbi     PORTD,lcdrs     ;Register select set for data
       nop
       sbi     PORTD,lcde      ;Toggle enable line
       nop
       cbi     PORTD,lcde
       ret
;=============================================
; subroutine waits for time equal to value in register timeout
;the register 'timeout' should be loaded before the call
delay:  tst     timeout
       brne    delay
       ret
;***************************************************************
;debounce state machine

debounce:	
        cpi      state,1	;jump to appropriate state
        breq    _key1
        cpi      state,2
        breq    _key2
        cpi      state,3
        breq    _key3
        cpi      state,4
        breq    _key4
_key1:
        rcall   kloop	;get button
        cpi     key,0
        brne    _key1no	;button pressed
                                ;_key1yes
        clr     press	
        ret
_key1no:
        mov     maybe,key
        ldi     state,2	;move to state 2
        ret
_key2:
        rcall   kloop
        cp      key,maybe
        brne    _key2no
                                ;_key2yes
        mov     press,key
        ldi     state,3	;move to state 3
        ret
_key2no:
        ldi     state,1	;mov to state 1
        ret
_key3:
        rcall   kloop
        cp      key,press
        brne    _key3no
                                ;_key3yes
        ret
_key3no:
        ldi     state,4	;move to state 4
        ret
_key4:  rcall   kloop
        cp      key,press
        brne    _key4no
                                ;_key4yes
        ldi     state,3	;go back to state 3
        ret
_key4no:
        clr     press           ;set press to 0
        ldi     state,1	;to state 1
        ret
;***************************************************************
;keypad monitor

kloop:  ldi     temp, 0x0f      ;set lower four lines to output
       out     DDRA, temp
       ldi     temp, 0xf0      ;and turn on the pullups on the inputs
       out     PORTA, temp
       nop                     ;Need some time for the pullups to
       nop                     ;charge the port pins
       nop
       nop
       nop                     ;Need some time for the pullups to
       nop                     ;charge the port pins
	nop                     
       nop
       nop
       nop                     
       nop 
       in      temp, PINA      ;read the high nibble
       mov     key, temp      ;and store it (with zeros in the low nibble)

       ldi     temp, 0xf0      ;set upper four lines to outputs
       out     DDRA, temp
       ldi     temp, 0x0f      ;and turn on pullups on the inputs
       out     PORTA, temp
       nop                     ;As before wait for the pin to charge
       nop                      
       nop
       nop
       nop
       nop
	nop                    
       nop
       nop
       nop                     
       nop 
       in      temp, PINA      ;read the low nibble
       or      key, temp       ;combine to make key code
	ret
;***************************************************************
timer2:	;timer 2 interrupt (enters every 1 second)
	in      savSREG, SREG
      push    temp
	push	ZL
	push	ZH

	ldi	temp,0b00000010
	eor	secflash,temp ;reverse secflash for blinking the seconds led
	inc 	seconds	;increment seconds since enters isr every second
	cpi	seconds, 60	;if seconds==60 need to reset to 0 and increment minutes
	brne	nochange
	clr	seconds
	inc	minutes
	cpi	minutes, 60	;if minutes== 60 need to reset to 0 and increment hours
	brne	nochange
	clr	minutes
	inc	hours
	cpi	hours, 24	;if hours==24 need to reset to zero and increment days
	brne	nochange
	clr	hours
	inc	date
	cpi	date,32	;if date==32 need to reset to 1 and increment month
	brne	cpdate31
	inc	month
	ldi	date,1
	rjmp	cpmonth13
cpdate31:		;if date==31 see if that is max for month
	cpi	date,31
	brne	cpdate30
	cpi	month,4	;April has 30 days, so increment month
	breq	incmonth
	cpi	month,6	;June has 30 days, so increment month
	breq	incmonth
	cpi	month,9	;September has 30 days, so increment month
	breq	incmonth
	cpi	month,11	;November has 30 days, so increment month
	brne	cpmonth13
	breq	incmonth
incmonth:
	inc	month
	ldi	date,1
	rjmp	cpmonth13
cpdate30:			
	cpi	date,30	
	brne	cpdate29
	cpi	month,2	;this will always switch from February to March 
	brne	cpmonth13
	inc	month
	ldi	date,1
	rjmp	cpmonth13
cpdate29:
	cpi	date,29	;if date==29 see if leap year and increment month
				;if month is February and not a leap year
	brne	cpmonth13
	cpi	month,2
	brne	cpmonth13
	mov	r31,year
chklp:	cpi	r31,0	;see if year is divisible by 4
	breq	islp
	cpi	r31,4
	breq	islp	
	subi	r31,4
	cpi	r31,99
	brpl	nolp
	rjmp	chklp
nolp:	inc	month
	ldi	date,1
islp:
cpmonth13:
	cpi	month,13	;if month==13 reset to 1
	brne	nochange
	ldi	month,1
	inc	year		;increment year is month==13
			
nochange:
	mov	temp, a1on
	cpi	temp,1	;if alarm is set to turn on check the time
	brne	iendt2
	cp	ahour,hours	;see if correct hour
	brne	endt2
	cp	amin,minutes ;see if correct minute
	brne	endt2

	cpi	seconds,5	;only go on for five seconds
	brpl	iendt2

	ldi	temp,0b00000011	;will output to portc to turn on 
;green led and sound alarm
	mov	secflash,temp
	rjmp	endt2
iendt2:	;don't sound alarm and complement led
	ldi	temp,0b00000010	
	and	secflash,temp
	ldi	temp,0b00000010
	eor	secflash,temp
	eor	secflash,temp
endt2:	
	out	PORTC,secflash	;output secflash to port to 
					;sound alarm(if needed) and light led (or not)
	pop	ZH
	pop	ZL
	pop     temp
      out     SREG, savSREG
	reti


;**************************************************************
;timer 0 ISR (timer-zero overflow)
;Enters every 1.0 mSec
timer0: in      savSREG, SREG
        push    temp
        push    ZL
        push    ZH
        dec     timeout
        ldi     temp,256-62
        out     TCNT0, temp     ; keeps clock ticking at 1 mSec
        ldi     temp,1
        add     thirtyms,temp
        ldi     temp,30		
        cp      thirtyms,temp	;clear 30ms counter if it equals 30
        brne    t0end
        clr     thirtyms
t0end:
        pop     ZH
        pop     ZL
        pop     temp
        out     SREG, savSREG
        reti                    ;back to backgound tasks
;**************************************************************
asciidate:		;put the date and alarm set information on led
	rcall	lcdclr
	clr	temp
	ldi	temp2,10
	mov	asciitemp,month
monthtens:			;count the number of tens in the months and
				;output that number to the lcd
	cp	asciitemp,temp2
	breq	nmonthtens
	cp	asciitemp,temp2
	brlo	Imonthones
nmonthtens:	inc	temp
	sub	asciitemp,temp2
	rjmp	monthtens
Imonthones:	ldi	temp2,0x30	;convert digit to ascii character
	add	temp,temp2
	rcall	lcdput
	clr	temp
	ldi	temp2,1
monthones:			
	cp	asciitemp,temp2
	breq	nmonthones
	cp	asciitemp,temp2
	brlo	monthdoner
nmonthones:	inc	temp
	sub	asciitemp,temp2
	rjmp	monthones
monthdoner:	ldi	temp2,0x30	;convert digit to ascii
	add	temp,temp2
	rcall	lcdput
	clr	temp
	ldi	temp,'/'	;put a slash in the date
	rcall 	lcdput
	clr	temp
	ldi	temp2,10
	mov	asciitemp,date
datetens:			;get the number of tens in the date and put on the lcd
	cp	asciitemp,temp2
	breq	ndatetens
	cp	asciitemp,temp2
	brlo	Idateones
ndatetens:	inc	temp
	sub	asciitemp,temp2
	rjmp	datetens
Idateones:	ldi	temp2,0x30	;convert to ascii
	add	temp,temp2
	rcall	lcdput
	clr	temp
	ldi	temp2,1
dateones:	
	cp	asciitemp,temp2
	breq	ndateones
	cp	asciitemp,temp2
	brlo	datedoner
ndateones:	inc	temp
	sub	asciitemp,temp2
	rjmp	dateones
datedoner:	ldi	temp2,0x30	;convert the ones digit to ascii
	add	temp,temp2
	rcall	lcdput
	clr	temp
	ldi	temp,'/'
	rcall 	lcdput
	clr	temp
	ldi	temp2,10
	mov	asciitemp,year
yeartens:		;get the number of tens in the year and put on the lcd
	cp	asciitemp,temp2
	breq	nyeartens
	cp	asciitemp,temp2
	brlo	Iyearones
nyeartens:	inc	temp
	sub	asciitemp,temp2
	rjmp	yeartens
Iyearones:	ldi	temp2,0x30	;convert to ascii
	add	temp,temp2
	rcall	lcdput
	clr	temp
	ldi	temp2,1
yearones:	
	cp	asciitemp,temp2
	breq	nyearones
	cp	asciitemp,temp2
	brlo	yeardoner
nyearones:	inc	temp
	sub	asciitemp,temp2
	rjmp	yearones

yeardoner:	ldi	temp2,0x30	;convert digit to ascii
	add	temp,temp2
	rcall	lcdput
	clr	temp
	ldi	temp,1
	cp	a1on,temp
	brne	a1noton	;if the alarm is not set to go on then finished
	ldi     temp,0xC0       ;Set address to last 8 chars
	rcall   lcdcmd
	ldi	temp,' '
	rcall	lcdput
	ldi	temp,'*'		;if alarm is set output "*ALARM*"
	rcall	lcdput
	ldi	temp,'A'
	rcall	lcdput
	ldi	temp,'L'
	rcall	lcdput
	ldi	temp,'A'
	rcall	lcdput
	ldi	temp,'R'
	rcall	lcdput
	ldi	temp,'M'
	rcall	lcdput
	ldi	temp,'*'
	rcall	lcdput
	ret
a1noton:
	ret


disptime:	;puts the time on the led display
	clr	temp
	ldi	temp2,10
	mov	timetemp,hours
hourtens:		;calculate the number of tens in the hour
	cp	timetemp,temp2
	breq	nhourtens
	cp	timetemp,temp2
	brlo	Ihourones
nhourtens:	inc	temp
	sub	timetemp,temp2
	rjmp	hourtens
Ihourones:
	ori	temp,0b01110000	;select first digit
	out	PORTB, temp		;output to port
	ldi	timeout, 4
	rcall	delay
	clr	temp
	ldi	temp2,1
hourones:	
	cp	timetemp,temp2
	breq	nhourones
	cp	timetemp,temp2
	brlo	hourdoner
nhourones:	inc	temp
	sub	timetemp,temp2
	rjmp	hourones
hourdoner:
	ori	temp, 0b10110000	;select second digit and 
	out	PORTB, temp		;output to port
	ldi	timeout, 4
	rcall	delay
	clr	temp
	clr	temp
	ldi	temp2,10
	mov	timetemp,minutes
mintens:				;calculate the number of tens in minutes
	cp	timetemp,temp2
	breq	nmintens
	cp	timetemp,temp2
	brlo	Iminones
nmintens:	inc	temp
	sub	timetemp,temp2
	rjmp	mintens
Iminones:
	ori	temp,0b11010000	;select the third digit and
	out	PORTB, temp		;output to the port
	ldi	timeout, 4
	rcall	delay
	clr	temp
	ldi	temp2,1
minones:	
	cp	timetemp,temp2
	breq	nminones
	cp	timetemp,temp2
	brlo	mindoner
nminones:	inc	temp
	sub	timetemp,temp2
	rjmp	minones
mindoner:
	ori	temp, 0b11100000	;select the fourth digit and
	out	PORTB, temp		;output to the port
	ldi	timeout, 4
	rcall	delay
	ret


a1disptime:				;same as disptime, but outputs alarm time to led
	clr	temp
	ldi	temp2,10
	mov	timetemp,ahour
a1hourtens:	
	cp	timetemp,temp2
	breq	a1nhourtens
	cp	timetemp,temp2
	brlo	a1Ihourones
a1nhourtens:	inc	temp
	sub	timetemp,temp2
	rjmp	a1hourtens
a1Ihourones:
	ori	temp,0b01110000
	out	PORTB, temp
	ldi	timeout, 4
	rcall	delay
	clr	temp
	ldi	temp2,1
a1hourones:	
	cp	timetemp,temp2
	breq	a1nhourones
	cp	timetemp,temp2
	brlo	a1hourdoner
a1nhourones:	inc	temp
	sub	timetemp,temp2
	rjmp	a1hourones
a1hourdoner:
	ori	temp, 0b10110000
	out	PORTB, temp
	ldi	timeout, 4
	rcall	delay
	clr	temp
	clr	temp
	ldi	temp2,10
	mov	timetemp,amin
a1mintens:	
	cp	timetemp,temp2
	breq	a1nmintens
	cp	timetemp,temp2
	brlo	a1Iminones
a1nmintens:	inc	temp
	sub	timetemp,temp2
	rjmp	a1mintens
a1Iminones:
	ori	temp,0b11010000
	out	PORTB, temp
	ldi	timeout, 4
	rcall	delay
	clr	temp
	ldi	temp2,1
a1minones:	
	cp	timetemp,temp2
	breq	a1nminones
	cp	timetemp,temp2
	brlo	a1mindoner
a1nminones:	inc	temp
	sub	timetemp,temp2
	rjmp	a1minones
a1mindoner:
	ori	temp, 0b11100000
	out	PORTB, temp
	ldi	timeout, 4
	rcall	delay
	ret

alm1set:				;sets the time for the alarm
	rcall	lcdclr
a1isettime:	clr     charcnt
        ldi     ZH, HIGH(setalarm<<1)	;output set alarm prompt
        ldi     ZL, LOW(setalarm<<1)

a1nextc:  lpm     ;r0             ;Get next character from flash
       	tst     r0              ;See if at end of message
       	breq    a1end1            ;If so, next message
       	cpi     charcnt,8       ;addressing changes at char #8!
       	brne    a1wrtit           ;at char 8, fix the addressing
       	ldi     temp,0xC0       ;Set address to last 8 chars
	rcall   lcdcmd
a1wrtit:  mov     temp,r0         ;Send it to the LCD
      	rcall   lcdput
       	adiw    ZL,1            ;Increment Z-pointer
       	inc     charcnt         ;keep track of chars on display
       	rjmp    a1nextc           ;Loop for more
a1end1:  	clr     charcnt
ai1sethour:
	ldi	temp,0
	mov	ahour,temp
	ldi	temp,1
	mov	butflag, temp	
a1sethour:					;set the hour
	ldi	temp,0
	cp	butflag,temp
	breq	a1nopress4
	ldi	temp, 29
	cp	temp, thirtyms
	brne	a1sethour
	rcall	a1disptime
	rcall	debounce
	cpi	state, 1
	brne	a1sethour
a1nopress4:
	ldi	temp,0
	mov	butflag,temp
	ldi	temp,29
	cp      temp,thirtyms
      brne    a1d1
	rcall	a1disptime
        rcall   debounce
a1d1:	cpi	press,up
      brne	a1next0
	ldi	temp,1
	mov	butflag,temp
	ldi	temp,1
	add	ahour,temp
	ldi	temp,24			;hour should not be 24
	cp	ahour,temp
	breq	a1zhour
	rjmp  	a1sethour
a1zhour:	ldi	temp,0		;reset hour to zero if incremented past 23
	mov	ahour,temp
	rjmp	a1sethour
a1next0:	cpi	press,down
	brne	a1next1
	ldi	temp,1
	mov	butflag,temp
	ldi	temp,1
	sub	ahour,temp
	ldi	temp,255		;ckeck if hour was decremented below 0
	cp	ahour,temp
	breq	a1mhour
	rjmp	a1sethour
a1mhour:	ldi	temp,23	;set hour to 23 if decremented below 0
	mov	ahour,temp
	rjmp	a1sethour
	clr	temp
	mov	amin,temp
a1next1:	cpi	press,set
	breq	a1isetmin
	brne	a1sethour
a1isetmin:
	clr	temp
	mov	amin,temp
	ldi	temp,1
	mov	butflag, temp				
a1setmin:
	ldi	temp,0
	cp	butflag,temp
	breq	a1nopress5
	ldi	temp, 29
	cp	temp, thirtyms
	brne	a1setmin 
	rcall	a1disptime
	rcall	debounce
	cpi	state, 1
	brne	a1setmin
a1nopress5:
	ldi	temp,0
	mov	butflag,temp
	ldi	temp,29
	cp      temp,thirtyms
      brne    a1d2 
	rcall	a1disptime
        rcall   debounce
a1d2:	cpi	press,up
        brne	a1next2
	ldi	temp,1
	mov	butflag,temp
	ldi	temp,1
	add	amin,temp
	ldi	temp,60			;minutes can't equal 60
	cp	amin,temp
	breq	a1zmin
	rjmp  	a1setmin

a1zmin:	clr	temp
	mov	amin,temp			;clear minutes if incremented past 59
	rjmp	a1setmin
a1next2:	cpi	press,down
	brne	a1next3
	ldi	temp,1
	mov	butflag,temp
	ldi	temp,1
	sub	amin,temp
	ldi	temp,255			
	cp	amin,temp			;check if minutes is below zero 
	breq	a1mmin
	rjmp	a1setmin
a1mmin:	
	ldi	temp,59
	mov	amin,temp			;set minutes to 59 if decremented below 0
	rjmp	a1setmin
	clr	temp
	mov	amin,temp
a1next3:	cpi	press,set
	breq	a1done
	brne	a1setmin
a1done:	
	ldi	temp,1
	mov	butflag,temp
	mov	a1on,temp
	ret