;RETURN TO THE MORSE BEACON PAGE

;Copy and paste this into an assembler file. 

;WARNING: A JMP IS USED IN THIS FILE, ALTHOUGH THE ATMEGA8 DOES NOT HAVE A JMP INSTRUCTION.
;THE LINE READS:
"jmp    Atodonoff". ONE POSSIBLE SOLUTION IS TO CHANGE THIS TO AN RJMP AND SEE IF THAT WORKS.
;ANOTHER IS TO IGNORE IT FOR NOW. IF YOU ASSEMBLER DOESN'T COMPLAIN, YOU CAN LEAVE FIXING THIS UNTIL LATER.
;AS FAR AS I KNOW THIS PART OF THE CODE WAS FULLY TESTED. WHY THE ASSEMBLER DID NOT COMPLAIN AND WHY THE CODE
;RAN CORRECTLY IS A MYSTERY AT THIS MOMENT. Noted March, 2007.

;-start of document-


;Program: Morse beacon with 4 A/D channels


;Version:morbecon050219A

;Copyright 2004, 2005 by the Dick Cappels and Jeff Heidbrier.
;projects(at)cappels.org www.projects.cappels.org
 
 
.include "m8def.inc"        ;Include file is in the same directory as the project.
 
     ;Interrupt timer parameters
     .equ    a1wpmhigh    =$12    ;High byte of number of clocks between interrupts.
     .equ    a1wpmlow    =$43    ;Low byte of number of clocks between interrupts.
     .equ    a5wpmhigh    =$03    ;High byte of number of clocks between interrupts.
     .equ    a5wmplow    =$A9    ;Low byte of number of clocks between interrupts.
     .equ    a10wpmhigh    =$01    ;High byte of number of clocks between interrupts.
     .equ    a10wpmlow    =$D4    ;Low byte of number of clocks between interrupts.
     .equ    a25wpmhigh    =$00    ;High byte of number of clocks between interrupts.
     .equ    a25wpmlow    =$BB    ;Low byte of number of clocks between interrupts.
     .equ    timer0rel1khz    =254    ;Reload value for tone timer. 254 = 1 kHz.
     .equ    timer0rel500hz    =252    ;Reload value for tone timer. 252 = 500 Hz.
 
         ;UART baud rate calculation
     .equ    clock = 4000000    ;clock frequency
     .equ    baudrate = 9600    ;choose a baudrate
    .equ    baudconstant = (clock/(16*baudrate))-1        
 
      ;ALLOCATE BUFFER(S)
     .equ    rambot    =$60
     .equ    lbuffsize    = 80    ;Bytes allocated to line buffer
     .equ    lbufftop    = rambot+80
     .equ    lbuffbot    = rambot ;Top address (start of) line buffer
     
 
     .def    opsel        = r2    ;Option select bits
     .def    termsel    = r3    ;Options as selected by terminal
     .def    tim0rel    = r4    ;Timer 0 reload value
     .def    EEchecksum    = r5    ;Simple checksum of EEPROM from $60 to $FE
     .def    temp        = r16    ;General purpose scratch register.
     .def    a1        = r17    ;Three byte number
     .def    a2        = r18    ;Three byte number
     .def    a3        = r19    ;Three byte number
     .def    h        = r20    ;Binary to decimal conversion.
     .def    t        = r21   ;Binary to decmial conversion.
     .def    u        = r22    ;Binary to decimal conversion.
     .def    flagreg    = r23    ;Flags.
     .def    temp2        = r24    ;Intermediate results
 
 
 ;EEPROM Map
 ;$60 to $B0 Line Buffer
 ;$FE        termsel byte
 ;$FF        simple checksum
 
 ;definiton of flagreg bit assignments
 ;0    Status of code out bit last sent (memory used to toggle)
 ;1    True enables toggling of code output
 ;2
 ;3
 ;4
 ;5
 ;6
 ;7
 
 
 ;defintion of opsel O(ption Select) bits
 ;0    lsb of code speed select (corresponds to port pin C4)
 ;1    msb of code speed select (correspoinds to port pin C5)
 ;2    lsb of A/D channels select (corrseponds to port p[in D2)
 ;3    msb of A/D channels select (corrseponds to port p[in D3)
 ;4    Tone Hi/low. 1 = 1 kHz; 0 = 500 Hz (corrsponds to port pin D4)
 ;5    Deault operation if 1 (corresponds to port pin D5)
 ;6
 ;7
 
 ;definition of termsel (terminal selection) bits -parameters set by RS-232 interface
 ;and stored in EEPROM.
 ;0    Terminal selections override user I/O selections when set. Can be over-ridden by groudning pin 11.
 ;1    Analog channel A on when set.
 ;2    Analog channel B on when set.
 ;3    Analog channel C on when set.
 ;4    Analog channel D on when set.
 ;5    lsb of code speed (corresponds to obsel bit 0).
 ;6    msb of code speed (corresponds to obsel bit 1).
 ;7    Tone Hi/low (corresponds to obsel bit 4).
 
 
 ;definition of I/O
 ;B0    + comparitor input (Reserved)
 ;B1    - comparitor input (Reserved)
 ;B2    Tone (Morse code) output    
 ;B3    Morse code output    
 ;B4    A/D channels 0    - configure as INPUT with weak pullup
 ;B5    A/D channels 1    - configure as INPUT with weak pullu
 ;B6    (not assigned - configure as INPUT with weak pullup)    
 ;B7    (not assigned - configure as INPUT with weak pullup)    
 
     .equ    PORTBdata    =0b11110000    ;Initial data    
     .equ    DDRBdata    =0b00001100    ;Initial data    
     .equ    codeport     = PORTB
     .equ    codeout    = DDRB
     .equ    codebit     = 2        ;Tone output
     .equ    pulsebit    = 3        ;Morse code output
 
 
 ;C0    A/D A    configure as INPUT, with weak pullup when not used
 ;C1    A/D B    configure as INPUT, with weak pullup when not used
 ;C2    A/D C    configure as INPUT, with weak pullup when not used
 ;C3    A/D D    configure as INPUT, with weak pullup when not used
 ;C4    Code Speed 0    - configure as INPUT with weak pullup
 ;C5    Code speed 1    - configure as INPUT with weak pullup
 ;C6    Reset pin - configure as INPUT with weak pullup
 ;C7    (does not exist - configure as INPUT with weak pullup)
 
     .equ    PORTCdata    =0b11110000    ;Initial data    
     .equ    DDRCdata    =0b00000000    ;Initial data
 
 
 ;D0    UART RECEIVE - configured with weak pullup
 ;D1    UART TRANSMIT
 ;D2    (not assigned - configure as INPUT with weak pullup)
 ;D3    (not assigned - configure as INPUT with weak pullup)
 ;D4    Tone Select    - configure as INPUT with weak pullup)
 ;D5    Default Op    - configure as INPUT with weak pullup)
 ;D6    (not assigned - configure as INPUT with weak pullup)
 ;D7    (not assigned - configure as INPUT with weak pullup)
 
     .equ    PORTDdata    =0b11111101    ;Initial data    
     .equ    DDRDdata    =0b00000010    ;Initial data

 
 .cseg    
 .ORG $0000    
rjmp     start
 .org $0009    
rjmp    timer0service    
                         ;Initializaton code

 start:                    ;Entry point after reset -initialize everything
 warm:                    ;Warm is actually a reset.
     ldi    temp,DDRBdata        ;Set PORTB.    
     out    DDRB,temp
     ldi    temp,PORTBdata
     out    PORTB,temp        
     ldi    temp,DDRCdata        ;Set PORTC
     out    DDRC,temp
     ldi    temp,PORTcdata
     out    PORTc,temp    
     ldi    temp,DDRDdata        ;Set PORTD.    
     out    DDRD,temp
     ldi    temp,PORTDdata
     out    PORTD,temp
     ldi    temp,high(ramend)     ;Initialize 16 bit Stack Pointer
     out    sph,temp    
     ldi     temp,low(ramend)    
     out     spl,temp
     clr    flagreg            ;Clear firmware flagreg (flag register).
 
                         ;SET UP USART
     clr    temp                ; Set baud rate
     out     UBRRH, temp
     ldi    temp,baudconstant        ;load computed value for baud rate
     out     UBRRL, temp            ;Enable Receiver and Transmitter
     ldi     temp, (1<<RXEN)|(1<<TXEN)
     out     UCSRB,temp            ;Set frame format: 8data, 2stop bit
     ldi     temp, (1<<URSEL)|(1<<USBS)|(3<<UCSZ0)
     out     UCSRC,temp
                         ;8 BIT TIMER 0 SETUP
     ldi    temp,5            ;Set prescaler for clk/8
     out    TCCR0,temp
     ldi    temp,timer0rel1khz    ;Set number of pulses to count up after division by prescaler
     mov    tim0rel,temp        ;Default is for 1 kHz (4 MHz clock).
     out    TCNT0,temp
     in    temp,TIMSK
     ori    temp,0b00000001        ;Enable timer 0 oveflow interrupt.
     out    TIMSK,temp
                         ;ITINITALIZE A TO D CONVERTER
     ldi    temp,0b00010101        ;Set control and status register. 4 MHz clock.Clear int flag.
     out    ADCSR,temp
     sei                    ;Enable interrupts.
                         ;Now that interrups are on and there is a tone, send the greeting.
 
     ldi    temp,0b11111100        ;25 words per minute
     mov    opsel,temp    
     rcall    setdottime            ;Set the dot period as a function of opsel bit 0,1
     rcall    crlf
     rcall    crlf
     rcall    crlf
     rcall    crlf
     rcall    Typeheader            ;Type the header at 25 WPM.
     rcall    Loadcommand            ;Load EEPROM contents into RAM $60 to $FF
     rcall    typestatus            ;Type terminal control setup.
     rcall    DumpLineBuffer        ;Display line buffer contents
     rcall    GetOptionBits        ;Get jumper selectable options to opsel register
                         ;Switch flow to Programmed Main if bit o in termsel is set,
                          ;EEPROM checksum is valid, and opsel bit 5 is set.
     ldi    temp,0b00100000        ;Check for jumper pin override.
     and    temp,opsel    
     breq    DefaultMain
     ldi    temp,0b00000001        ;Check for terminal program control bit set in termsel
     and    temp,termsel
     breq    DefaultMain    
     clr    YH                ;Check EEProm checksum
     ldi    YL,$FF
     ld    temp,Y
     cp    temp,EEChecksum
     brne    DefaultMain
     rjmp    ProgrammedMain
         
     
 DefaultMain:                ;Main Loop
     rcall    GetOptionBits        ;Get jumper selectable options to opsel register
     rcall    setdottime            ;Set the dot period as a function of opsel bit 0,1
     rcall    ToggleTonepitch        ;Set tone pitch based on opsel bit 4
     rcall    MeasureAndSendVolts
     rcall    interword
     rcall    OptionsEditor        ;Check to see if Operator requested Options Editor.
     rjmp    DefaultMain    
     

     
 ToggleTonepitch:                ;Set the interrupt period to 500 Hz or 1 Khz
     push    temp                ;based on opsel bit 4.
     mov    temp,opsel
     andi    temp,0b00010000
     breq    x22
     ldi    temp,timer0rel1khz
     rjmp    x23
 x22:    ldi    temp,timer0rel500hz    
 x23:
     mov    tim0rel,temp        ;Set interrupt time for chosen tone frequ.
     pop    temp
     ret
     
 
 
     
 GetOptionBits:                ;Get jumper selectable options to opsel register
     push    temp
     in    temp,PINC            ;Get Port C bits 4,5.
     andi    temp,0b00110000
     lsr    temp
     lsr    temp
     lsr    temp
     lsr    temp
     mov    opsel,temp
     in    temp,PIND            ;Get Port D bits 2,3,4, and 5.
     andi    temp,0b00111100
     or    opsel,temp
     pop    temp
     ret
 
 
 crlf:                    ;Send Carrige return and line feed ($0D, $0A)
     push    temp
     ldi    temp,$0D
     rcall    emitchar
     ldi    temp,$0A
     rcall    emitchar
     pop    temp
     ret
 
 emitchar0D:                ;Send outchar to terminal. Add line feed to carriage return.
     push    temp
     rcall    emitchar
     cpi    temp,$0D            ;Its a carraiage return, send a linefeed also
     brne    notareturn
     ldi    temp,$0A
     rcall    emitchar    
 notareturn:   
     pop    temp
     ret
 
 
 emitchar:    ;Send character contained in temp.
     sbis    UCSRA,UDRE            ;Test for TX register empty
     rjmp    emitchar            ;Loop until TX empty
     out    UDR,temp            ;Send the byte
     ret
     
 getchar:    
     sbis    UCSRA,RXC            ;Wait until a character has been received
     rjmp    getchar
     in    temp,UDR            ;Read byte from the UART
     ret
 
 
 Typeheader:                ;Type header
     push    ZL
     push    ZH
     ldi    ZH,high(2*hellomessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*hellomessage)    ;Load low part of byte address into ZL
     rcall    typeromstring        ;Send it
     pop    ZH
     pop    ZL
     ret
     
     
     
 hellomessage:
     .db    $0A,$0D
     .db    $0A,$0D
     .db   "morbecon050219A "
     .db    $0A,$0D
     .db   $00,$00
 
 
 sendromstring:            ;call with location of string in Z.
     push    ZL            ;Save Z on stack.
     push    ZH
 srs1:
          lpm            ;Load byte from program memory into r0.
         tst    r0            ;Check if we've reached the end of the message.
         breq    finishsendstering    ;If so, return.
      mov    temp,r0
     rcall    SendMorseAscii     ;Send upper case ASCII Char as Morse Code.
          adiw    ZL,1        ;Increment Z registers
          rjmp    srs1
 finishsendstering:
     pop    ZH            ;Pop Z from stack.
     pop    ZL
      rcall    interword
          ret
 

 
 MeasureAndSendVolts:        ;Measure 1 to 4 A/D channels and send the values as Morse Code
                     ;and via RS-232 accoding to obsel bits 2 and 3.
                     ;Bit 3        Bit 2    Measure
                     ;1        1    Channel A only (ADC  0)
                     ;0        1    Channels A & B (ADC 0,1)
                     ;1        0    Channels A,B & C (ADC 0,1,2)
                     ;0        0    Channels A,B,C & D (ADC 0,1,2,3)
     push    temp
    ldi    temp,'A'
     rcall    SendMorseAscii
 
     ldi    temp,0            ;Channel A always sent, so do that first.
     rcall    measure            ;Measure it.
     rcall    SendVolts            ;Send out as Morse Code
     mov    temp,opsel
     andi    temp,0b00001100
     cpi    temp,0b00001100        ;If bit 2 and 3 are set, we're done.
     breq    donemeas
     push    temp
      ldi    temp,$20
     rcall    SendMorseAscii
     ldi    temp,'B'
     rcall    SendMorseAscii
     ldi    temp,1            ;Do Channel B.
     rcall    measure            ;Measure it.
     rcall    SendVolts            ;Send out as Morse Code
     pop    temp
     cpi    temp,0b00000100        
     breq    donemeas            ;If only bit 2 is set, we're done.    
     push    temp
     ldi    temp,$20
     rcall    SendMorseAscii
     ldi    temp,'C'
     rcall    SendMorseAscii
     ldi    temp,2            ;Do Channel C..
     rcall    measure            ;Measure it.
     rcall    SendVolts            ;Send out as Morse Code
     pop    temp
     cpi    temp,0b00001000        
     breq    donemeas            ;If only bit 3 is set, we're done.    
     ldi    temp,$20
     rcall    SendMorseAscii
     ldi    temp,'D'
     rcall    SendMorseAscii
     ldi    temp,3            ;Do Channel D..
     rcall    measure            ;Measure it.
     rcall    SendVolts            ;Send out as Morse Code
donemeas:                    ;We are done.
     ldi    temp,$20
     rcall    SendMorseAscii    
     ldi    temp,$0A
     rcall    SendMorseAscii
     ldi    temp,$0D
     rcall    SendMorseAscii
     pop    temp
     ret
 
 
 
 Measure:    ;Measure A/D channel. Enter with channel number in temp. Exit with data in YH:YL
         ;Allowed range is 0..5
     push    temp
     sbi    ADCSR,ADEN            ;Enable A/D converter.
     andi    temp,0b00000011        ;Mask off upper bits to restrict range of channel selction.
     ori    temp,0b01000000        ;Set reference voltage bit.
     out    ADMUX,temp            ;Select channel.
     sbi    ADCSR,ADSC            ;Start conversion.
 wfc:
     sbis    ADCSR,ADIF            ;Wait for bit to be set, indicating conversion complete.
     rjmp    wfc
     sbi    ADCSR,ADIF            ;Clear interrupt flag.
     in    YL,ADCL            ;Get data into Y register.
     in    YH,ADCH
     pop    temp
     ret    
     
 sendcodedcode:                ;Send Coded Morse Code
                         ;Shift out morse code from coded character.
                         ;Enter with code for character in temp.
     
 ;Description of data format from David Robinson's web page:
 ;"At this point I was reminded of the N1KDO NHRC-2 repeater controller published
 ;in February 97 QST that had Morse ID. Investigation of the assembler listing (1)
 ;revealed a simple conversion scheme, where all morse characters are encoded in a
 ;single Byte, bitwise, LSB to MSB.; 0 = dit, 1 = dah. The Byte is shifted out
 ;to the right, until only a 1 remains. As an example 3 is encoded as binary 00111000,
 ;which translates to 38 in hexadecimal. " The code that follows is based on this technique.
 
 morecode:
     cpi    temp,0b00000001
     breq    codedcodesent
     clc
     ror    temp
     brcs    senddash            ;Send a dash if lsb was a one
     rcall    dot                ;Send a dot if lsb was not a one
     rjmp    morecode
 senddash:
     rcall    dash
     rjmp    morecode
 codedcodesent:                ;Finished sending the coded code.
     ret
 
 
 SendMorseAscii:    ;Look up coded Morse code and send, followed by rcall to interchar.
         ;Enter with ASCII character in temp. Upper-case, don't process
         ;control characters.

     rcall    OptionsEditor        ;Check to see if Operator requested Options Editor.        
     push    ZL                ;Save registers
     push    ZH
    push    temp                ;Save contents of temp.
     rcall    emitchar0D            ;Emit the char via UART.
     pop    temp                ;Restore value of temp.
     cpi    temp,$20            ;If space character, do interword delay.
     brne    SMA1
     rcall    interword
     rjmp    lookupdone
 SMA1:
     cpi    temp,$5B
     brmi    upperacse    
     andi    temp,$5F            ;Make upper-case
 upperacse:
     cpi    temp,$2A    
     brmi    lookupdone
                        ;Set up pointer into codechart.
     ldi    ZH,high(2*codechart)    ;Load high part of byte address into ZH.
     ldi    ZL,low(2*codechart)    ;Load low part of byte address into ZL.
     subi    temp,$2A            ;Removed offset from ASCII value in temp.
     add    ZL,temp            ;Add the value to the index.
     clr    temp
     adc    ZH,temp
     lpm                    ;Fetch the value from the table.
     mov    temp,r0
     rcall    sendcodedcode        ;Send as Morse Code
     rcall    interchar            ;Dealy one interchar time
 lookupdone:
     pop    ZH                ;Restore registers
     pop    ZL
     ret                    ;Return
 
 
 dot:        ;Send dot, wait one dot time.
     sbr    flagreg,0b00000010        ;Set flag to send tone.
     sbi    codeport,pulsebit        ;Set on-off key pulse high.
     rcall    dottime
     cbr    flagreg,0b00000010    ;Clear flag to send tone.
     cbi    codeport,pulsebit        ;Set on-off key pulse low.
     rcall    dottime
     ret
 
 
 dash:    ;Send dash, wait one dot time.
     sbr    flagreg,0b00000010    ;Set flag to send tone.
     sbi    codeport,pulsebit        ;Set on-off key pulse high.
     rcall    dottime
     rcall    dottime
     rcall    dottime
     cbr    flagreg,0b00000010    ;Clear flag to send tone.
     cbi    codeport,pulsebit        ;Set on-off key pulse low.
     rcall    dottime
     ret
 
 interchar:    ;Wait interchear period with output off -3 dot times
     rcall    dottime
     rcall    dottime
     rcall    dottime
     ret
     
 interword:    ;Wait interword period with output off-6 dot times
     rcall    dottime
     rcall    dottime
     rcall    dottime
     rcall    dottime
     rcall    dottime
     rcall    dottime
     rcall    dottime
     ret
 
 
 setdottime:                
     push    temp
     
                     ;Load compare registers, OCR1AH,OCR1AL with values for
                     ;dot rate as a function of opsel bits 0 and 1.
                     ;
                     ;    bit1    bit0    Code Speed    OCR1AH    ORC1Al
                     ;    1        1        10 WPM
                     ;    1        0        1  WPM
                     ;    0        1        5  WPM
                     ;    0        0        25 WPM
                     ;
                     ;Note Code speed is calcualted using PARIS (50 spaces)
                     ;send in 1 minute = 1 WPM.
 
 
     mov    temp,opsel              ;Get option select bits into temp.
     andi    temp,0b00000011        ;Mask off all but two lsb.
     cpi    temp,0                  ;Test if 0.
     brne    not0                   ;If not 0 skip to next test.
     ldi    temp,a25wpmhigh         ;If 0 load parameters for 25 WPM.
     out    OCR1AH,temp
     ldi    temp,a25wpmlow
     out    OCR1AL,temp    
     rjmp    speedset
 not0:    
    cpi    temp,1                ;Test for value = 1.
     brne    not1
     ldi    temp,a5wpmhigh
     out    OCR1AH,temp
     ldi    temp,a5wmplow
     out    OCR1AL,temp    
     rjmp    speedset
 not1:    cpi    temp,2        ;Test for value = 2
     brne    not2
     ldi    temp,a1wpmhigh
     out    OCR1AH,temp
     ldi    temp,a1wpmlow
     out    OCR1AL,temp    
     rjmp    speedset
 not2:    
    ldi    temp,a10wpmhigh    ;Its not 0,1, or 2, so it must be 3.
     out    OCR1AH,temp
     ldi    temp,a10wpmlow
     out    OCR1AL,temp    
 speedset:                    ;Come to here when speed has been set.
     pop    temp
     ret
 
 
 
 dottime:                    ;Delay one dot time.
 
     push    temp                    
     ldi    temp,0b00001101        ;Set timer 1 to reset 0000 after compare match. Prescaler = 1X.    out    TCCR1B,temp
     out    TCCR1B,temp
 
 
 
 wd1:    in    temp,TIFR
     sbrs    temp,OCF1A             ;Wait for flagreg bit two to go high (timer to time out)
     rjmp    wd1
     out    TIFR,temp            ;Clear the flag
 
     ldi    temp,0b00000000        ;Set timer 1 to "normal" mode, prescale output stopped.
     out    TCCR1B,temp
     pop    temp
 
     ret
 
    
 SendVolts:
                         ;Enter with input value in YH:YL. YH,YL,a1,a2,a3,temp,H,T,U modified.
                        ;Scale input with range of 0 to 1023 to d digit expression of range
                         ;from 0 to 5. This is for a 5 volt full scale input 10 bit ADC.
                         ;Multiply input by 489 and divide by 1,000 to get answer in tens of
                         ;millivolts.
 
     push    temp    
     clr    a1                ;Clear the 3 byte number
     clr    a2
     clr    a3
     
         
 mloop:    
         
     tst    YL        
     brne    notzero
     tst    YH
     brne    notzero
     rjmp    countdone
 notzero:
     sbiw    YL,1                ;Decrement the 10 bit value and add 489 to each time
     ldi    temp,$E9
     add    a1,temp            ;To multiply number in Y by 489
     ldi    temp,$01
     adc    a2,temp
     clr    temp
     adc    a3,temp
     rjmp    mloop
 countdone:                    ;At this point, the product is in a1,2,3
                         ;Test values come out of 489000 here.
     clr    H
     clr    T
     clr    U
 MoreH:    
     inc    H    
     subi    a1,$A0            ;Find out how many 100,000's
     sbci    a2,$86
     sbci    a3,1
     brcc    MoreH    
     ldi    temp,$A0            ;Subtracted one too many, add back on.
     add    a1,temp
     ldi    temp,$86
     adc    a2,temp
     ldi    temp,1
     adc    a3,temp
     dec    H                ;VALUE EXITING THIS ROUTINE IS 23112. SHOULD BE 89000.
 MoreT:
     inc    T    
     subi    a1,$10            ;Find out how many 10.000's
     sbci    a2,$27
     sbci    a3,$00
     brcc    moreT        
     ldi    temp,$10            ;Subtracted one too many, add back on.
     add    a1,temp
     ldi    temp,$27
     adc    a2,temp
     ldi    temp,0
     adc    a3,temp
     dec    T
 MoreU:
     inc    U    
     subi    a1,$E8            ;Find out how many 10.000's
     sbci    a2,$03
     sbci    a3,$00
     brcc    moreT    
     ldi    temp,$E8            ;Subtracted one too many, add back on.
     add    a1,temp
     ldi    temp,$03
     adc    a2,temp
     ldi    temp,0
     adc    a3,temp
     dec    U                
     subi    H,-48                ;Convert to ASCII and send. Send H
      mov    temp,H
     rcall    SendMorseAscii
     subi    T,-48
      mov    temp,T
     rcall    SendMorseAscii
     subi    U,-48                ;Send U
      mov    temp,U
      rcall    SendMorseAscii
     rcall    interword
     rcall    interword
     rcall    interword
     pop    temp
     ret
 
 
 
 ;/////////////////////////////Morse Code Chart\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\
 
 codechart:    ;Coded Morse Code look up table. Use ASCII value -$30, so zero = 0, "A" = $11, etc.
 ;Note: Some ASCII characters are silent, and are coded as 0b00000001
 ;Also note: BT (pause) is coded for ASCII "<" and SK (end of contanct) is coded for ASCII "*",
 ;and End of Message is coded for ASCII "+".
 

;    * (SK)        + (End of Message)
.db    0b01101000,    0b00101010


;    ,(comma)    -          .          /
.db    0b01110011,0b1011110,0b01111010,0b00101001


;    0          1          2          3
.db    0b00111111,0b00111110,0b00111100,0b00111000

;    4          5          6          7
.db    0b00110000,0b00100000,0b00100001,0b00100011
     
 
;    8          9          :          ;
.db    0b00100111,0b00101111,0b01000111,0b01010101
      
     
;    <  (BT)        =          >          ?
.db    0b000110001,0b00000001,0b00000001,0b01001100
          
 ;    @          A          B          C
.db    0b00000001,0b00000110,0b00010001,0b00010101
 
 
 ;    D          E          F          G
.db    0b00001001,0b00000010,0b00010100,0b00001011
 
  ;    H          I          J          K
.db    0b00010000,0b00000100,0b00011110,0b00001101
 
 
  ;    L          M          N          0
.db    0b00010010,0b00000111,0b00000101,0b00001111
 
 
   ;    P          Q          R          S
.db    0b00010110,0b00011011,0b00001010,0b0001000
   
 
    ;    T          U          V          W
.db    0b00000011,0b00001100,0b00011000,0b00001110
   

    ;    X          Y          Z          [
.db    0b00011001,0b00011101,0b00010011,0b00000001
   
     
 
 ;/////////////////////////////Interrupt 0 to create tone\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\
 timer0service:
     push    temp    
     in    temp,sreg
     push    temp
    mov    temp,tim0rel        ;Set number of pulses to count up after division by prescaler
     out    TCNT0,temp
     sbrs    flagreg,1
     rjmp    notoggle
                         ;Toggle tone output
     sbi    codeout,codebit        ;Enable code output pin.
     mov    temp,flagreg        ;Toggle it, using flagreg 0 as memory of last one.
     andi    temp,0b00000001
     inc    temp
     andi    temp,0b00000001
     brne    codehigh
     cbi    codeport,codebit
     andi    flagreg,0b11111110
     rjmp    toggledone
 codehigh:
     sbi    codeport,codebit
     ori    flagreg,0b00000001
 toggledone:
     pop    temp
     out    sreg,temp
     pop    temp
     reti                    ;Return from interrupt.
     
 notoggle:    ;Don't toggle port, but delay to equalize interrupt time toggling and not toggling.
     cbi    codeout,codebit        ;Disable code out pin.
     nop
     nop
     nop
     nop                    ;sing interupts for dot and tone, this equalization won't be needed anymore.
     nop    
     nop
     rjmp    toggledone
     reti
 
 
 
 
 ;/////////////////////////////Setup via RS-232 Terminal\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\
 
typestatus:                    ;Type the user teminal controls setup
     rcall    GetOptionBits        ;Get jumper selectable options to opsel register
     rcall    Checkpin11            ;Check to see if Pin 11 is grounded.            
     rcall    ShowADOnOff            ;Show status of A/D channels
     rcall    ShowTermSetting        ;Show Status of terminal control
     rcall    ShowWPM            ;Show WPM
     rcall    ShowTone            ;Show tone settings    
     ret
 
 
 OptionsEditor:                ;Allow user to set options via RS-232.
                         ;Check to see if return character ($0D) is in UART recveive buffer.
                         ;If no $0D, return to calling routine.
                         ;If it is $0D, then enter editor to edit options.
     
 chk1:    sbis    UCSRA,RXC        ;Check for character
     ret                    ;If no character, return
     in    temp,UDR            ;Read byte from the UART
     cpi    temp,$0D
     breq    HaveCR
     rjmp    chk1                ;Continue to check for CR until buffer empty. Return if no $0D.
 HaveCR:                    ;Start Editor
     cli                    ;Stop interrupts while in options editor
     rcall    crlf
     rcall    crlf
     rcall    typestatus
     rcall    EditorGreeting        ;Print greeting and menu.
     rcall    getchar            ;Get a character from the terminal.
     rcall    crlf        
     andi    temp,$5F            ;Make character upper-case.
     cpi    temp,'A'    
     breq    Atodonoffj            ;Toggle A/D channels on and off.
     cpi    temp,'B'    
     breq    EnterTextj            ;Enter text.
     cpi    temp,'C'
     breq    ToggleTerminalj        ;Toggle terminal override of jumpers ON/OFF.
     cpi    temp,'D'
     breq    SetWPMj            ;Set code speed.
     cpi    temp,'E'
     breq    ToggleTonej            ;Toggle between 500Hz and 1 kHz tone
     cpi    temp,'X'
     breq    DoneOptons
     rjmp    HaveCR
     
 DoneOptons:
     rcall    TypeStoringMessage    ;Save setup data
     rcall    SaveCommand
     rcall    crlf
     rjmp    warm                ;Warm start
 Atodonoffj:
     jmp    Atodonoff
 EnterTextj:
     jmp    EnterText
 ToggleTerminalj:
     jmp    ToggleTerminal
 SetWPMj:
     jmp    SetWPM
 ToggleTonej:
     jmp    ToggleTone    
     
     
 Checkpin11:                ;Check pin 11 of the chip directly (port pin D5)
     sbis    PIND,5
     rcall    WarnPin11
     ret
     
 WarnPin11:                    ;Warn that pin 11 is grounded
     push    ZL
     push    ZH
     ldi    ZH,high(2*Pin11message)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*Pin11message)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
     
 
 
 TypeOFFMessage:    ;Type labels for status of A/D inputs    
     push    ZL
     push    ZH
     ldi    ZH,high(2*OFFMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*OFFMessage)    ;Load low part of byte address into ZL
     rcall    typeromstring        ;Send it
     pop    ZH
     pop    ZL
     ret
 
 OFFMessage:
     .db    "OFF   "
     .db     $00,$00
     
     
 TypeSelectAChannelmessage:        ;Type labels for status of A/D inputs    
     push    ZL
     push    ZH
     ldi    ZH,high(2*SelectAChannelmessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*SelectAChannelmessage)    ;Load low part of byte address into ZL
     rcall    typeromstring                ;Send it
     pop    ZH
     pop    ZL
     ret
 
 SelectAChannelmessage:
     .db    "Select a channel to toggle ON/OFF or X to eXit >  "
     .db     $00,$00
 
 ShowADOnOff:
     rcall    TypeAnalogChannelMessage ;Put up the menu, position cursor for ON/OFF status.
     ldi    temp,$20
     rcall    emitchar        
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     rcall    emitchar
     mov    temp2,termsel
     ror    temp2                ;Get channel a flag into carry
     ror    temp2
     brcc    noA
     rcall    TypeONMessage        ;Display either "ON" or "OFF" depending on
     rjmp    HaveA                ;State of bits corresponding to channels A..D.
 noA:    call    TypeOFFMessage
 HaveA:    
    ror    temp2
     brcc    noB
     rcall    TypeONMessage
     rjmp    HaveB
 noB:    
    call    TypeOFFMessage
 HaveB:    ror    temp2
     brcc    noC
     rcall    TypeONMessage
     rjmp    HaveC
 noC:    
    call    TypeOFFMessage
 HaveC:    
    ror    temp2
     brcc    noD
     rcall    TypeONMessage
     rjmp    HaveD
 noD:    
    call    TypeOFFMessage
 HaveD:
     rcall    crlf
     ret
 
 
 Atodonoff:                    ;Turn A/D Channels on and off.
     rcall    ShowADOnOff            ;Show status of A/D channels
     rcall    crlf
     rcall    TypeSelectAChannelmessage
     rcall    getchar
     andi    temp,$5F            ;Make upper-case
     cpi    temp,'A'
     breq    toggleA
     cpi    temp,'B'
     breq    toggleB
     cpi    temp,'C'
     breq    toggleC
     cpi    temp,'D'
     breq    toggleD
     cpi    temp,'X'
     breq    ad1
     rjmp    Atodonoff
 ad1:
     rcall    crlf
     rjmp    HaveCR            ;Return to calling menu
 
 
 
 toggleA:
     ldi    temp,0b0000010
     eor    termsel,temp
     rjmp    Atodonoff
     
 toggleB:
     ldi    temp,0b0000100
     eor    termsel,temp
     rjmp    Atodonoff
     
 toggleC:
     ldi    temp,0b0001000
     eor    termsel,temp
     rjmp    Atodonoff
     
 toggleD:
     ldi    temp,0b0010000
     eor    termsel,temp    
     rjmp    Atodonoff
     

 
 TypeAnalogChannelMessage:            ;Type labels for status of A/D inputs    
     push    ZL
     push    ZH
     ldi    ZH,high(2*Analogchanelmessage);Load high part of byte address into ZH
     ldi    ZL,low(2*Analogchanelmessage)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
     
 
 Analogchanelmessage:                ;Labels for status of A/D inputs
     .db    $0A,$0D
     .db    "Channel:    A     B     C     D "
     .db    $0A,$0D     
     .db     $00,$00
 
 
 TypeOnMessage:                    ;Type labels for status of A/D inputs    
     push    ZL
     push    ZH
     ldi    ZH,high(2*OnMessage)        ;Load high part of byte address into ZH
     ldi    ZL,low(2*OnMessage)        ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
 
 OnMessage:
     .db    "ON    "
     .db     $00,$00
 
 
     
 Pin11message:                ;Message warning that pin 11 is grounded.
     .db    $0A,$0D
     .db     "OPTIONAL OPERATION EDITOR."
     .db    $0A,$0D
     .db     "********************************************************************"
     .db    $0A,$0D
     .db     "****         WARNING: PIN 11 (DIP PACKAGE) IS GROUNDED.         ****"
     .db    $0A,$0D
     .db     "****    Changes can be saved, but all software selected options ****"
     .db    $0A,$0D
     .db     "****    are disabled while pin 11 is grounded.                  ****"
     .db    $0A,$0D
     .db     "********************************************************************"
     .db    $0A,$0D
     .db    $0A,$0D
     .db     $00,$00
 
 
 EditorGreeting:                ;Type editor greeting
     push    ZL
     push    ZH
     ldi    ZH,high(2*Editorhellomessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*Editorhellomessage)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
     
     
     
 Editorhellomessage:            ;Options editor greeting.
     .db    $0A,$0D
     .db     "OPTIONAL OPERATION EDITOR."
     .db    $0A, $0D
     .db    "Menu of Programmable Options"
     .db    $0A,$0D
     .db    $0A,$0D
     .db    "A......Turn analog channels on or off "
     .db    $0A,$0D
     .db    "B......Enter a text message "
     .db    $0A,$0D
     .db    "C......Toggle Terminal Settings enable/disable"
     .db    $0A,$0D
     .db    "D......Set Morse Code Speed "
     .db    $0A,$0D
     .db    "E......Toggle tone frequency between 500 Hz and 1 kHz "
     .db    $0A,$0D
     .db    "X......eXit this menu and return to normal operation"
     .db    $0A,$0D
     .db    $0A,$0D
     .db     "Please select an operation by typing"
     .db    $0A,$0D
     .db    "A,B,C,D,E, or X."
     .db    $0A,$0D
     .db    "> "
     .db     $00,$00
 

 
 getterminalline:             ;Get characters from terminal into linebuffer. Stop accepting chars except
                         ;0D when end of buffer is reached.
     ldi    temp,$3E
     rcall    emitchar
     ldi    YH,$00            ;Initialize line buffer pointer to lbufftop
     ldi    YL,lbufftop
 anothertermchar:
     rcall    getchar            ;Get char from terminal
     cpi    temp,$08            ;Is it backspace/delet character?
     breq    deletekey
     st    Y,temp            ;Put in line buffer
     cpi    temp,$0D
     breq    CRreceived            ;If char was CR,then return
     cpi    YL,lbuffbot            ;If buffer is at last byte, don't store char but beep.
     brne    notlbuffend    
     ldi    temp,$07            ;If not CR at last position, ring the bell
     rcall    emitchar
     rjmp    anothertermchar
 notlbuffend:
     dec    YL                ;Not end of buffer and not CR, so emit and go another
 echoandgo:
     push    temp
     rcall    emitchar0d
     pop    temp
     rjmp    anothertermchar
 CRreceived:                ;Last char in line received
     ret
     
 
     
 deletekey:                    ;Backup up cursor -destructive backspace
     cpi     YL,lbufftop
     brne    notexceededbuftop
     ldi    temp,$07            ;If not CR at last position, ring the bell
     rcall    emitchar
     rjmp    anothertermchar
 notexceededbuftop:
     rcall    emitchar0d
     inc     YL
     ldi    temp,$0D
     st    Y,temp            ;Put in line buffer
     rjmp    anothertermchar
     
 
 
 DumpLineBuffer:                ;Dump line buffer until $0D is reached.
     ldi    YH,$00            ;Initialize line buffer pointer to lbufftop
     ldi    YL,lbufftop
     clr    XL
 ALBC:
     ld    temp,Y            ;Get char from linebuffer
     dec    YL
     inc    XL
     rcall    emitchar
     cpi    YL,lbuffbot
     breq    HitBuffEnd
     cpi    XL,80
     breq    HitBuffEnd
     cpi    temp,$0D
     brne    ALBC                ;If char was not CR,then do it again
 ;    ldi    temp,$0A
 ;    rcall    emitchar
 HitBuffEnd:
     ret
 
 
 typeromstring:                ;Type on RS-232 terminal screen call with location of string in Z.
     push    ZL                ;Save Z on stack.
     push    ZH
 srsa1:
          lpm                ;Load byte from program memory into r0.
         tst    r0                ;Check if we've reached the end of the message.
         breq    finishsendsteringA    ;If so, return.
          mov    temp,r0
     rcall    emitchar            ;Sends only via RS-232.
          adiw    ZL,1            ;Increment Z registers
          rjmp    srsa1
 finishsendsteringA:
     pop    ZH                ;Pop Z from stack.
     pop    ZL
          ret
 
 
 
 Savecommand:                ;Store RAM from $60 to $FF EEPROM.        
 
     clr    YH
     ldi    YL,$FE
     st    Y,termsel
     rcall    GenChecksum            ;Generate simple checksum for RAM $FE to $60
                         ;and place value in EEchecksum
    clr    YH
     ldi    YL,$FF
     st    Y,EEChecksum
     cli                    ;Stop interrupts while writing EEPROM
     clr     YH
     clr    ZL    
     ldi    YL,$FF
     ldi    ZL,$FF
 storeanotherchar:
     ld    temp,Y            ;Put contents of program memory into temp.
 wrat1:    sbic    eecr,eewe        ;Wait for EEPROM write to not be busy.
     rjmp    wrat1
     out    eearL,ZL                
     out    eearH,ZH
     out    eedr,temp            ;Set up the  write data.
     sbi    eecr,eemwe
     sbi    eecr,eewe            ;Trigger the write.
     cpi    YL,$60
     breq    finishedsaving
     dec    ZL
     dec    YL
     rjmp    storeanotherchar
 finishedsaving:
     sei    ;Enable interrupts now that EEPROM write is complete.
     ret
     
     
 
 Loadcommand:    ;Restore Page 0 from EEPROM. ;Also save termsel register in EEPROM inside page zero.
     clr     YH
     clr    ZH    
     ldi    YL,$FF
     ldi    ZL,$FF
 loadanotherchar:
 wratz1:    sbic    eecr,eewe        ;Wait for EEPROM write to not be busy
     rjmp    wratz1
     out    eearL,ZL            ;Move to EEPROM address register
     out    eearH,ZH    
     sbi    eecr,eere            ;Trigger the read
     in    temp,eedr            ;Get the data into temp
     st    Y,temp
     cpi    YL,$60
     breq    finishedloading
     dec    ZL
     dec    YL
     rjmp    loadanotherchar
 finishedloading:
     clr    YH
     ldi    YL,$FE
     ld    termsel,Y
     rcall    GenChecksum            ;Generate simple checksum for RAM $FE to $60
                         ;and place value in EEchecksum
    ret
 
 
 EnterText:
     rcall    crlf                ;Send return and linefeed.
     rcall    TypeCurrentlyStoredMessage
     rcall    DumpLineBuffer
     rcall    crlf
     rcall    TypePleaseTypeMesage
     rcall    getterminalline    
     jmp    HaveCR
     
 
 
 TypeStoringMessage:        
     push    ZL
     push    ZH
     ldi    ZH,high(2*StoringMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*StoringMessage)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
 
 StoringMessage:
     .db    $0A,$0D
     .db    $0A,$0D
     .db    "Please wait about 2 seconds, now storing setup parameters in EEPROM."
     .db    $0A,$0D
     .db   $00,$00
         
 TypeCurrentlyStoredMessage:                
     push    ZL
     push    ZH
     ldi    ZH,high(2*CurrentlyStoredMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*CurrentlyStoredMessage)    ;Load low part of byte address into ZL
     rcall    typeromstring                ;Send it
     pop    ZH
     pop    ZL
     ret
 
 CurrentlyStoredMessage:
     .db    "The line below contains the currently stored text message "
     .db    $0A,$0D
     .db   $00,$00
         
     
 TypePleaseTypeMesage:            
     push    ZL
     push    ZH
     ldi    ZH,high(2*PleaseTypeMesage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*PleaseTypeMesage)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
 
 PleaseTypeMesage:
     .db    "Please enter text message to be stored. "
     .db    $0A,$0D
     .db    "Maximum 80 characters on one line."
     .db    $0A,$0D
     .db   $00,$00    
     
 ToggleTerminal:
     ldi    temp,0b00000001
     eor    termsel,temp
     jmp    HaveCR
     
         
 ShowTermSetting:
     mov    temp,termsel
     andi    temp,0b00000001    
     breq    termoff
     rcall    TypeTypeTermONMessage
     ret
 termoff:
     rcall    TypeTypeTermOFFMessage
     ret
     
 TypeTypeTermONMessage:            
     push    ZL
     push    ZH
     ldi    ZH,high(2*TypeTermONMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*TypeTermONMessage)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
 
 TypeTermONMessage:
     .db    "Options set by terminal are ENABLED."
     .db    $0A,$0D
     .db   $00,$00        
     
     
 TypeTypeTermOFFMessage:            
     push    ZL
     push    ZH
     ldi    ZH,high(2*TypeTermOFFMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*TypeTermOFFMessage)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
 
 TypeTermOFFMessage:
     .db    "Options set by terminal are DISABLED. "
     .db    $0A,$0D
     .db   $00,$00        
     
         
     
 SetWPM:
     rcall    ShowWPM
     ldi    temp,0b10011111            ;Clear code speed bits (to 25 WPM)
     and    termsel,temp    
 PTM:    
     rcall    TypeEnterCodeSpeedMessage
     rcall    getchar
     andi    temp,$5F
     rcall    emitchar
     cpi    temp,'A'
     breq    set1
     cpi    temp,'B'
     breq    set5
     cpi    temp,'C'
     breq    set10
     cpi    temp,'D'
     breq    set25
     rjmp    PTM
     
 set1:    ;Set bits in register
     ldi    temp,0b01000000
     or    termsel,temp
     rjmp    WPMSetDone
 
 
 
 set5:        ;Set bits in register
     ldi    temp,0b00100000
     or    termsel,temp
     rjmp    WPMSetDone
 
 
 
 set10:        ;Set bits in register
     ldi    temp,0b01100000
     or    termsel,temp
     rjmp    WPMSetDone
 
 
 set25:                    ;Bits alread set to zero.
     
 
 
 
 WPMSetDone:    
     rcall    crlf
     rjmp    HaveCR            ;Return to calling menu
     
 ShowWPM:
     rcall    TypeCodeSpeedSetMessage    ;Type start of message
     mov    temp,termsel        ;Load temset byte into temp
     andi    temp,0b01100000
 
     cpi    temp,0b01100000        ;Test for 10 WPM
     breq    x10WPM
     cpi    temp,0b01000000        ;Test for 1 WPM
     breq    x1WPM
     cpi    temp,0b00100000        ;Test for 5 WPM
     breq    x5WPM
                         ;If here, assume 25 WPM.
     ldi    temp,'2'
     rcall    emitchar
     ldi    temp,'5'
     rcall    emitchar
     rjmp    wpmdispdone
 
 x10WPM:    ldi    temp,'1'
     rcall    emitchar
     ldi    temp,'0'
     rcall    emitchar
     rjmp    wpmdispdone
     
     
 x1WPM:    ldi    temp,'1'
     rcall    emitchar
     rjmp    wpmdispdone
     
 x5WPM:    ldi    temp,'5'
     rcall    emitchar
     rjmp    wpmdispdone        
     
 wpmdispdone:
     rcall    crlf    
     ret
 
 
 TypeCodeSpeedSetMessage:            
     push    ZL
     push    ZH
     ldi    ZH,high(2*CodeSpeedSetMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*CodeSpeedSetMessage)        ;Load low part of byte address into ZL
     rcall    typeromstring                ;Send it
     pop    ZH
     pop    ZL
     ret
 
 
 CodeSpeedSetMessage:
     .db    "Code Speed in Words Per Minute: "
     .db     $00,$00        
     
 
 
 TypeEnterCodeSpeedMessage:            
     push    ZL
     push    ZH
     ldi    ZH,high(2*EnterCodeSpeedMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*EnterCodeSpeedMessage)    ;Load low part of byte address into ZL
     rcall    typeromstring                ;Send it
     pop    ZH
     pop    ZL
     ret
 
 
 EnterCodeSpeedMessage:
     .db    $0A,$0D
     .db    "Enter the letter that corresponds to the"
     .db    $0A,$0D
     .db    "code speed desired. "
     .db    $0A,$0D
     .db    "A....1 Word Per Minute"        
     .db    $0A,$0D
     .db    "B....5 Words Per Minute "
     .db    $0A,$0D
     .db    "C....10 Words Per Minute"
     .db    $0A,$0D
     .db    "D....25 Words Per Minute"
     .db    $0A,$0D
     .db    $0A,$0D
     .db    "Please enter A,B,C,or D > "    
      .db    $00,$00        
     

 
 ToggleTone:
     ldi    temp,0b10000000
     eor    termsel,temp
     jmp    HaveCR
     
         
 ShowTone:
     mov    temp,termsel
     andi    temp,0b10000000    
     breq    ToneLow
     rcall    TypeToneHighMessage
     ret
 ToneLow:
     rcall    TypeToneLowMessage
     ret
     
 TypeToneHighMessage:            
     push    ZL
     push    ZH
     ldi    ZH,high(2*ToneHighMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*ToneHighMessage)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
 
 ToneHighMessage:
     .db    "Tone output is set to 1 kHz."
     .db    $0A,$0D
     .db   $00,$00        
 
 
 TypeToneLowMessage:            
     push    ZL
     push    ZH
     ldi    ZH,high(2*ToneLowMessage)    ;Load high part of byte address into ZH
     ldi    ZL,low(2*ToneLowMessage)    ;Load low part of byte address into ZL
     rcall    typeromstring            ;Send it
     pop    ZH
     pop    ZL
     ret
 
 ToneLowMessage:
     .db    "Tone output is set to 500 Hz. "
     .db    $0A,$0D
     .db   $00,$00        
 
 GenChecksum:                ;Generate simple checksum for RAM $FE to $60
                         ;and place value in EEchecksum
     clr    EEchecksum
     clr    YH
     ldi    YL,$FE
 summore:
     ld    temp,Y    
     add    EEchecksum,temp        ;(no carry)
     cpi    YL,$60
     breq    checksumdone
     dec    YL
     rjmp    summore
 checksumdone:
     ret
 
 
 ProgrammedMain:                ;This will:
                         ;copy control bits from termsel to opsel
                         ;Set code speed
                         ;Set tone
                         ;Send text string
                         ;Sample analog channels
             
     rcall    GetOptionBits        ;Get jumper selectable options to opsel register.
     rcall    MoveTermselToOpsel    ;Copy needed bits from terminal setup.
     rcall    setdottime            ;Set the dot period as a function of opsel bit 0,1.
     rcall    ToggleTonepitch        ;Set tone pitch based on opsel bit 4.
                         ;Setup complete
                     
 contp:    
    rcall    SendTextString    ;Send the text string
     rcall    MeasureAndSendProgVolts    ;Send selected A to D channels
     rcall    OptionsEditor        ;Check and see if user send carriage return, calling editor
     rcall    SendSilence            ;Send some silence (wait a while)
     rjmp    contp                ;Send it again.
 
 
 
 MoveTermselToOpsel:
                         ;Move termsel bits below to corresponding opsel bits.
 ;defintion of opsel O(ption Select) bits
 ;0    lsb of code speed select (corresponds to port pin C4)
 ;1    msb of code speed select (correspoinds to port pin C5)
 ;4    Tone Hi/low. 1 = 1 kHz; 0 = 500 Hz (corrsponds to port pin D4)
 
 ;definition of termsel (terminal selection) bits -parameters set by RS-232 interface
 ;5    lsb of code speed (corresponds to obsel bit 0).
 ;6    msb of code speed (corresponds to obsel bit 1).
 ;7    Tone Hi/low (corresponds to obsel bit 4).
 
 
 
     mov    YL,termsel
     andi    YL,0b10000000        ;Get bit 7.
     lsr    YL
     lsr    YL
     lsr    YL                ;Get into bit 4 position.
     mov    temp,termsel
     andi    temp,0b01100000        ;Get bits 5 and 6.
     lsr    temp
     lsr    temp
     lsr    temp
     lsr    temp
     lsr    temp                ;Get bits into 0 and 1 positions.
     or    temp,YL            ;Get the values of bits for 0,1, and 4 into one register
     push    temp
     mov    temp,opsel
     andi    temp,0b11101100
     mov    opsel,temp
     pop    temp
     or    temp,opsel            ;Use of bits from jumpers, esp. D5.
     mov    opsel,temp            ;shoot code above not tested.
     ret
 
 
 SendTextString:                ;If more than $0D in buffer,Dump line buffer until
                          ;$0D reached to a max of 80 chars.
     rcall    crlf
     rcall    interword
     ldi    YH,$00            ;Initialize line buffer pointer to lbufftop
     ldi    YL,lbufftop
     clr    XL
 ALBC2:
     ld    temp,Y            ;Get char from linebuffer
     dec    YL
     inc    XL
     rcall    SendMorseAscii
     cpi    YL,lbuffbot
     breq    HitBuffEnd2
     cpi    XL,80
     breq    HitBuffEnd2
     cpi    temp,$0D
     brne    ALBC2                ;If char was not CR,then do it again
     rcall    interword
     rcall    interword
 HitBuffEnd2:
     ret
 
 
 
 
 
 
 
 MeasureAndSendProgVolts:    ;Measure 1 to 4 A/D channels and send the values as Morse Code
                     ;and via RS-232 accoding to obsel bits 2 and 3.
                 
 ;definition of termsel (terminal selection) bits -parameters set by RS-232 interface
 ;and stored in EEPROM.
 ;1    Analog channel A on when set.
 ;2    Analog channel B on when set.
 ;3    Analog channel C on when set.
 ;4    Analog channel D on when set.
                 
                 
     push    temp
     mov    temp,termsel        ;See if this channel is to be sent.
     andi    temp,0b00000010
     breq    noAtoday
     ldi    temp,'A'
     rcall    SendMorseAscii
     ldi    temp,0
     rcall    measure            ;Measure it.
     rcall    SendVolts            ;Send out as Morse Code.
     ldi    temp,$20
     rcall    SendMorseAscii
 noAtoday:
     mov    temp,termsel        ;See if this channel is to be sent.
     andi    temp,0b00000100
     breq    noBtoday
     ldi    temp,'B'
     rcall    SendMorseAscii
     ldi    temp,1    
     rcall    measure            ;Measure it.
     rcall    SendVolts            ;Send out as Morse Code.
     ldi    temp,$20
     rcall    SendMorseAscii
 noBtoday:
     mov    temp,termsel        ;See if this channel is to be sent.
     andi    temp,0b00001000
     breq    noCtoday
     ldi    temp,'C'
     rcall    SendMorseAscii
     ldi    temp,2    
     rcall    measure            ;Measure it.
     rcall    SendVolts            ;Send out as Morse Code.
     ldi    temp,$20
     rcall    SendMorseAscii
 noCtoday:
     mov    temp,termsel        ;See if this channel is to be sent.
     andi    temp,0b00010000
     breq    noDtoday
     ldi    temp,'D'
     rcall    SendMorseAscii
     ldi    temp,3    
     rcall    measure            ;Measure it.
     rcall    SendVolts                ;Send out as Morse Code.
     ldi    temp,$20
     rcall    SendMorseAscii
 noDtoday:
                         ;We are done.
     ldi    temp,$20
     rcall    SendMorseAscii    
     ldi    temp,$0A
     rcall    SendMorseAscii
     ldi    temp,$0D
     rcall    SendMorseAscii    
     pop    temp
     ret
 
 
 SendSilence:                ;Delay between sequences
     ldi    temp,10
     CS:    rcall    interword            ;interword is not supposed to damage temp.
     dec    temp
     brne    CS
     ret
 
 
 .exit
 
March of 2007: Removed "
.include "tn12def.inc" ;Note that no path is given for this file."  It was a cut-and-paste artifact that was commented out.
March of 2007: Also corected a typographical error in "
.equ    PORTCdata    =0b11110000    ;Initial data "
March of 2007: Noted that the line 
"jmp    Atodonoff"." contains the jmp instruction which the ATMEGA8 does not support.

Liability Disclaimer and intellectual property notice (Summary: No warranties, use these pages at your own risk. You may use the information provided here for personal and educational purposes but you may not republish or use this information for any commercial purpose without explicit permission.)

I neither express nor imply any warranty for the quality, fitness for any particular purpose or user, or freedom from patents or other restrictions on the rights of use of any software, firmware, hardware, design, service,information, or advice provided, mentioned,or made reference to in these pages. By utilizing or relying on software, firmware, hardware, design, service,information, or advice provided, mentioned, or made reference to in these pages, the user takes responsibility to assume all risk and associated with said activity and hold Richard Cappels and Jeff Heidbrier harmless in the event of any loss or expense associated with said activity. The contents of this web page, unless otherwise noted, is copyrighted by Richard Cappels and  Jeff Heidbrier. Use of information presented on this site for personal, nonprofit educational and noncommercial use is encouraged, but unless explicitly stated with respect to particular material, the material itself may not be republished or used directly for commercial purposes. For the purposes of this notice, copying binary data resulting from program files, including assembly source code and object (hex) files into semiconductor memories for personal, nonprofit educational or other noncommercial use is not considered republishing. Entities desiring to use any material published in this pages for commercial purposes should contact the respective copyright holder(s).  

-end of document-

;RETURN TO THE MORSE BEACON PAGE