; Notice - This software was written by Steve Weber, KD1JV ; ; This particular version includes some additions by Nick Kennedy, WA5BDU ; ; 9/14/08 - Selectable 9850 / 9851 modes working; Rotary encoder working. ; ; V3 ; ; this version is a sort of starting over from a clean copy to try to get ; the 9850 option working. I got the other one so screwed up that I'm ; modifying a working version bit by bit with frequent testing. ; ; Original author's statement: ; ;Analog Devices AD9851 controller program for atmel "Butterfly" demo board. ;by KD1JV for hobby use only ; More WA5BDU comments: ; Steve's use of the 'flags' register -- ; flags = r19 ; ; b0 not used, I'm using as clear for 9851 set for 9850 ; b1 rapid tune mode ; b2 XIT enabled ; b3 RIT enabled ; b4 sidetone enabled ; b5 dash ; b6 dot ; b7 straight key mode ; I think the RC oscillator is running at 8 MHz, which I believe gives ; a 125 ns instruction cycle time. CKSEL isn't explicitly set in ; this code, but it defaults to use of the RC oscillator ... ; ; The Butterfly also has a 32,767 Hz crystal which is the time base ; for timer2, used by the program. ; ; I'm adding comments to Steve's source code because as ; of starting this project I know nothing about AVR assembly ; or the Butterfly ; ; A couple of things I'd like to try are - ; ; 1) Add rotary encoder input for frequency control ; 2) Add a "switch" to go between AD9850 and AD9851 versions ; with separate reference frequency calibration for ; each and also the required change to the command byte ; to the DDS. ; ; I have Joe Pardue's document "Butterfly Alternate Pin Uses" ; from AVR Freaks website and www.smileymicros.com to assist ; in finding unused pins or pins that can be diverted. ; ; So, I'm going to try to use pins assigned to the JTAG connector, which ; is just to the right of the connector I'm using to go to the DDS-60. ; ; Per Joe Pardue, I can use Port F pins 4, 5, 6, 7. They can be used for ; ADC but I'm sure they work as digitals too. To do this, I need to disable ; JTAG by setting the JTD bit in the MCUSCR register. Note, the PDF shows ; this register as MCUCR on page 235. JTD is bit 7. Write it twice!!! ; ; Here's Port F from the top, of J402, that is ... ; 10 8 6 4 2 ; 9 7 5 3 1 ; I'm going to use PF4 and PF5 which are pins 1 & 5 respectively ; (of the J402 connector, not the chip ...) ; ; PF4 = Pin 1 = INPUT A ; PF5 = Pin 5 = INPUT B ; ; Note also PF6 (3), PF7 (9), GND (2), Vcc (4) ; ; So I need to set their data directions and whatever else ... ; ; To use ports (example: port f) for general I/O, there are three ; registers DDRF, PORTF, and PINFn where n represents the bit. ; ; For the data direction (DDRx), 1 is for output and 0 is for input ; ; While the pin is configured as an input, writing a 1 to the corresponding ; bit of PORTx, the pull-up resistor is turned on. If the the pin ; is configured as an output, then writing 1s to the bits of PORTx ; makes the corresponding pins high, and 0 makes them low, as expected. ; ; I'm about out of registers, so I'm going to use GPIOR0 for another ; flags register. There are 3 general purpose I/O registers, gpior0, 1, 2 ; and of those gpior0 is below address $020, so it can be acted on by ; opcodes SBI, CBI, SBIS, SBIC. Same bits of GPIOR0 as of port f (4 & 5) ; are used to store the status of port F 4 & 5. Bits 0 and 1 are used ; to flag to program code that an Up or Down step is in process. Yeah, I ; should have just use a SRAM location -- plenty to spare. ; ; ******* PINS USED BY KD1JV FOR INTERFACE TO THE DDS CARD ************ ; ******* AND USE OF SPI INTERFACE TO SEND FREQ DATA TO DDS *********** ; ; Uses J400 or PORTB connector, lower left corner of the butterfly ; ; Pins: ; ; 2 4 6 8 10 ; 1 3 5 7 9 ; ; 9 is GND, 10 is V+ ; ; PIN signal name(s) DDS usage ; 1 PB0 (-SS) freq-sync (load) ; 2 PB1 (SCK) clock ; 3 PB2 (MOSI) data ; ; See other comments throughout this file where the SPI is configured and used, ; for more explanation ... ; ; The SPI does the data bits and clocking via the MOSI and SCK lines. It's ; still possible to manipulate as normal portb pins, which is done in the ; program also ... ; *************** JOYSTICK TO BITS DEFINITIONS ******************** ; ; This info is not in the Butterfly documentation; you can't even ; get it from the schematic unless you know the pin letters of the ; stick and their correspondence to the stick positions ... Note that ; they're split between ports B and E, so watch those typing fingers ; ; With the port pin pull-ups ON, these bits will read SET when the switch ; is not operated and CLEAR when it is ... ; ; Position port - bit ; ; IN B 4 ; LEFT E 2 ; RIGHT E 3 ; UP B 6 ; DOWN B 7 ; ; Steve's use of EEPROM: ; rdeed reads a byte of eeprom at eadr and increments eadr ; wreed writes a byte of eeprom at eadr and increments eadr ; in both cases, register mrenc carries the data being written or read ; ; 4 bytes from 0 to 3 store ref_fre (reference frequency) info, which is ; used unless the high byte is $FF, then the default values are used. ; ; 8 bytes from 4 thru $0C are used, 4 for foffset (static ram start $01A0) ; and 4 bytes for boffset, (static ram start $01A4). It doesn't appear ; that the higher 4 bytes at boffset are used. Program doesn't use ; this label and no access higher than foffset + 3 ; So for my plan to allow embedding data for the AD9850 version in addition ; to that for the AD9851 will start at eeprom location $0C and go thru $0F ; I'll also use address $10 to store a flag for the last configuration chosen, ; so the program can start up with the last configuration. I'm going to store ; 50 decimal for the AD9850 version and anything else ($FF, or whatever), will ; mean use the default AD9851 information. ; When I find the value 50 in eeprom [$10], I'll change the flags[0] bit to ; 1 to tell routines we're addressing a AD9850 at 100 MHz ; ; So, 9850 ref_fre data at $0C - $0F eeprom, and flag at $10 ; ; IF Offset for the 9850 version will start at $11 and go thru $14 ; NRK - There are 32 registers (8 bit) in the GP register file, r0 -- r31 ; mapped into address space 00 - 1F ; ; The last six (r26 - r31) are the X, Y, & Z registers ; (two 8-bit registers each), which can be used for indirect addressing, ; including 16 bit with features like auto increment or decrement of the ; pointer. As 8-bit registers, they're called xl, xh, yl, yh, zl, zh. ; ; ******** On writing to LCDs ***************** ; The program already has the bit patterns set up for common ASCII characters ; and numbers. It starts at segtable and has them in sequence of 0 thru 9 and ; then A thru Z. Four bytes per character. ; ; The address of the 1st byte for 'N' should be at ... ; ; segtable + 40 + ('N'-'A')*4, but beware because addressing data in ; program memory isn't that straighforward. See app note AVR108 for info. ; Here's the big GOTCHA - program memory addresses point to 16 bit words, not ; to bytes. You use the LPM opcode to access individual bytes, using the Z ; register to indirectly address memory. Z must contain the address times 2 ; and the lowest bit of Z (b0) will contain 0 to address the low byte and 1 to ; address the high byte. ; In the addressing above, the constant '40' is to get past chars 0 - 9, so if ; you want a number, leave it out. Then (chr - 'A') * 4 points to the actual ; character ; ; The character map information is stored in nybbles of four bytes of ; memory for each character. The driver in the ATMega169 takes that ; information and drives the actual segments. There are six available digits ; ; 2 3 4 5 6 7 ; ; for the even numbered digits (2, 4, 6), the info goes into the low nybble ; and for the odd numbered digits (3, 5, 7) it goes into the high nybble ; .include "m169def.inc" ;give the working registers names .def dd0 =r0 .def dd1 =r1 .def dd2 =r2 .def dd3 =r3 .def dd4 =r4 .def dd5 =r5 .def dd6 =r6 .def dd7 =r7 .def dv0 =r8 .def dv1 =r9 .def dv2 =r10 .def dv3 =r11 .def dr0 =r12 .def dr1 =r13 .def dr2 =r14 .def dr3 =r15 .def cnt1 =r0 .def temp =r16 .def temp1 =r17 .def eadr =r18 .def flags =r19 .def dotcnt =r20 .def cdak =r21 .def dlycnt =r22 .def kcnst =r23 .def tcnst =r24 .def dly =r25 .def mrenc =r26 .def bcdd =r16 .def bcds =r18 .def fbin0 =r4 .def fbin1 =r5 .def fbin2 =r6 .def fbin3 =r7 .def bcd0 =r8 .def bcd1 =r9 .def bcd2 =r10 .def bcd3 =r11 ;give the sram locations names .equ fbcd =$17b .equ fbcd0 =$17c .equ fbcd1 =$17d .equ fbcd2 =$17e .equ fstep =$170 .EQU ftword =$174 .equ bstep =$178 .equ block2 =$08 .equ block1 =$0c .equ fsk =$160 .equ ritb =$188 .equ foffset =$1a0 .equ boffset =$1a4 ; boffset label not used in program ... .equ frcv =$184 .equ ritr =$18c .equ srcv =$190 .equ fbin =$198 .equ ref_fre =$194 .equ bndp =$161 .equ ddsen =0 .equ clock =1 .equ data =2 .equ cdsp =$162 .equ csdigit =$163 .equ bndigit =$164 .equ chrn1 =$150 .equ chrn2 =$151 .equ chrn3 =$152 .equ chrn4 =$153 .equ chrn5 =$154 .equ chrn6 =$155 .equ rbcd0 =$156 .equ rbcd1 =$157 .equ rbcd2 =$158 .equ atbcd0 =8 .equ atbcd3 =11 ; ************************************************************************ ; A MACRO to put characters to the LCD: ; in the macro below, note that available positions left to right are ; 2, 3, 4, 5, 6, 7 ; and character is an ASCII numeral or upper case char code such as 'A' .MACRO put1char ; character, position ldi temp, @0 ldi temp1, @1 call put1 .ENDMACRO ; Note that macros have to appear before they're used ... ; *********************************************************************** ; A MACRO to delay certain # of dlycnt units using timer2 ; ; I think a dlycount is about 256 ms or a quarter second ; Use with single parameter # of counts ; .MACRO delayq ; DELAYQ, Q MEANS quarter second ldi dly,255 ; start with full house count clr dlycnt cpi dlycnt, @0 brne PC-1 ; keep checking .ENDMACRO ; ************************************************************************ .org $0000 ;interupt reset vector address jmp reset reti nop reti nop reti nop jmp timer2 reti nop ;begin the program reset: clr temp ;this loop clears all the control registers clr zh ldi zl,$20 ;start the loop at the control register address wipe: st z+,temp ;store the byte and increment pointer cpi zl,$61 ;stop at calosc word brne wipe ldi zl,$6b ;continue on mwipe: st z+,temp cpi zl,$c4 brne mwipe ldi temp,$08 sts assr,temp ;set up stack pointer ldi temp,low(ramend) out spl,temp ldi temp,high(ramend) out sph,temp ;set up I/O port b ldi temp,$f8 out portb,temp ldi temp,$27 out ddrb,temp ;set up I/O port e ldi temp,$bf out porte,temp ldi temp,$c0 out ddre,temp ; V3 stuff added *********************** ; *** NRK ADD -- TURN OFF JTAG SO CAN USE PINS FOR ; *** OPTICAL ENCODER KNOB ; ; What kind of memory is MCUCR? Apparently, I treat it like ; a port ... in temp, MCUCR sbr temp, 0b10000000 ; set JTD to turn off JTAG out MCUCR, temp out MCUCR, temp ; write it TWICE! ; ******** THIS ACTUALLY WORKED -- I COULDN'T USE PORT F UNTIL ******** ; ********* I WROTE THE JTD bit of MCUCR twice !!! ******************* ;set up I/O port f ; NRK changes - port f 4 & 5 will be my encoder inputs ; make them inputs and turn on pull-ups ; existing code makes 2 & 3 outputs and the rest inputs, so ; I'm OK there ... ; ldi temp,$0c ; out portf,temp ldi temp,$0c ; bits 2 & 3 set to be outputs; others inputs out ddrf,temp ldi temp, 0b00111100 ; this is original 0x0c plus 4 & 5 pull-ups out portf, temp clr flags ;clear the flags register ; ********* V3 TEST - CLEAR BIT 0 OF FLAGS FOR 9851 MODE ****** ; Here, I'll write a decimal 50 to flag eeprom byte $10 to show ; 9850 mode, then my code will "find" it and set the flag ... ; ; This test did work OK ; ; ldi eadr, $10 ;addr of flag ; ldi mrenc, 50 ; call wreed ; write 50 to $10 eeprom ; nop cbr flags,1 ; assume 9851 mode with flag clear ; next, I come along and find the flag ... ldi eadr, $10 ; flag DDS-30 or -60 call rdeed ; returns with data in mrenc cpi mrenc, 50 brne not_50 sbr flags,1 ; set flag to mean 9850 mode not_50: ;set up the lcd control registers, must be done in this order! ldi temp,$b7 sts lcdcrb,temp ldi temp,$03 sts lcdfrr,temp ldi temp,$0f sts lcdccr,temp lcdset: ldi temp,$80 ;turns on LCD sts lcdcra,temp ckofs: rcall set_ref_f ; set reference frequency from eeprom or default ;check for IF offset data (below was re_3) ldi yl,low(foffset) ;load lsd sram start address of IF offset sram location ldi yh,high(foffset) ;into indirect address pointer clr temp out eearh,temp ; high byte of address ldi eadr,$04 ; load eeprom location assuming 9851 sbrc flags,0 ; 9850 version has bit set ldi eadr,$11 ; 9850 version eeprom starts here ***** V3 ***** ldi temp1,8 moff: call rdeed ;read eeprom st y+,mrenc ;store the data into sram dec temp1 brne moff lds temp,foffset+3 ;check data cpi temp,$ff brne rst1 ;branch if okay test: clr temp ;clear IF offset if not okay sts foffset,temp sts foffset+1,temp sts foffset+2,temp sts foffset+3,temp ;initialize binary frequency step data rst1: ldi temp,$64 ; 100 Hz step sts fstep,temp clr temp sts fstep+1,temp sts fstep+2,temp sts fstep+3,temp ;set up serial peripheral interface register ldi temp,$70 out spcr,temp ;set up registers with inital values initreg: rcall init_dds ldi temp,$09 sts tccr2a,temp ;set up timer2 ldi temp,28 sts ocr2a,temp init2: lds temp,assr ;check for T2 ocrub2 bit sbrc temp,1 rjmp init2 clr temp sts tifr2,temp ldi temp,15 sts cdsp,temp ;code speed pointer ldi cdak,$19 ;20 wpm code speed timer data ldi temp,$01 sts fsk,temp ;frequency step constant pointer ldi temp,$20 sts csdigit,temp ;bcd code speed ldi temp,$02 sts timsk2,temp ;turn on timer 0 interupt sei ;enable general interups *** TIMER2 functional ; ********* V3 - with timer2 running, here's where I'll test my ; print to screen and delay ... ; rcall saynick ; ********* V3 test ; delayq 20 ; this did work. Put NICK to LCD for about 5 seconds ; ; *************************************************** V3 ; ; I'm going to put a release number to the screen for 1.25 seconds put1char 'V', 2 put1char 'Z'+1, 3 ; SPACE char is stored after 'Z' char put1char '1', 4 put1char 'Z'+3, 5 ; DASH (minus) char is stored at Z+3 put1char '0', 6 delayq 5 ; At this point, I want to put to the screen which chip we're controlling ; for a couple seconds ... put1char 'A', 2 put1char 'D', 3 put1char '9', 4 put1char '8', 5 put1char '5', 6 put1char '0', 7 ; tentative ... sbrc flags,0 ; bit set means currently 9850, rjmp dontput1 put1char '1', 7 dontput1: delayq 6 ; keep it on screen for ~1.5 seconds sbis pine,5 ;check paddle input for straight key sbr flags,$80 ;set flag if detected ldi temp,$e1 sts admux,temp ldi temp,$02 sts didr0,temp ldi temp,$c7 sts adcsra,temp ; turns ADC on ; here the program checks the ADC input to see if the ; voltage coded band selection has changed adwait: lds temp,adcsra sbrc temp,6 rjmp adwait clr temp sts adcsra,temp ; turns ADC off set lds temp,adch cpi temp,85 brsh lb_06 ; branch if same or higher ... cpi temp,75 brsh lb_10 cpi temp,65 brsh lb_12 cpi temp,55 brsh lb_15 cpi temp,45 brsh lb_17 cpi temp,35 brsh lb_20 cpi temp,25 brsh lb_30 cpi temp,15 brsh lb_40 cpi temp,5 brsh lb_80 ldi temp,0 rjmp bd9 lb_80: ldi temp,1 rjmp bd9 lb_40: ldi temp,2 rjmp bd9 lb_30: ldi temp,3 rjmp bd9 lb_20: ldi temp,4 rjmp bd9 lb_17: ldi temp,5 rjmp bd9 lb_15: ldi temp,6 rjmp bd9 lb_12: ldi temp,7 rjmp bd9 lb_10: ldi temp,8 rjmp bd9 lb_06: ldi temp,9 rjmp bd9 ;switch polling loops ; wait1 loops until none of the four inputs listed is closed ; at the start of each loop it delays 256 clocks for debounce ... ; this is used after any switch action, to make sure the switch ; has re-opened before allowing another switch action (function) ; at the end, the rapid tune flag for UP/DOWN tuning is cleared wait1: clr temp swbd: dec temp brne swbd sbis pine,3 ; RIGHT rjmp wait1 sbis pinb,4 ; IN rjmp wait1 sbis pinb,6 ; UP rjmp wait1 sbis pinb,7 ; DOWN rjmp wait1 cbr flags,$02 ;clear rapid tune flag bit (bit 1) wait: sbrc flags,7 ;check for straight key mode flag bit rjmp wait3 ;jump around if so sbis pine,4 ;check for paddle closure rjmp padin ;jump to paddle routine sbis pine,5 ;check for paddle closure rjmp padin ;jump to paddle routine wait2: sbis pinb,6 ;check for frequency tune UP rjmp tune ;jump to frequency tune routine sbis pinb,7 ;check for frequency tune DOWN rjmp tune ;jump to frequency tune routine sbis pinb,4 ;check for change frequency tuning rate rjmp step ;jump to change frequency tuning rate routine sbis pine,3 ;check for RIT button rjmp rit ;jump to rit routine sbis pine,2 ;check function button rjmp kfunc ;jump to functions routine ; *********** ENCODER SCAN **************************************** ; ; ; I'll insert my port f encoder scan code here. At the end I need to ; rjmp to wait to keep this loop intact ; ; I did this once using my flip-flop hardware to produce separate ; trains of UP and DOWN pulses, but re-did it to use the raw data, ; which was actually an easier programming task. ; ; I'm going to use gpior0 bit 0 set to mean up-step in progress and ; gpior0 bit 1 set to mean down-step in progress, to signal Steve's ; other step up and down routines. So clear them first ... ; ; The operation of the A and B logic states is ; ; for CW rotation, when A goes high, B will be low and ; when A goes low, B will be high ... ; ; for CCW rotation, when A goes high, B will be high and ; when A goes low, B will be low ; ; So, my routine will read the A and B states ... ; ; If A has not changed since previous, exit routine ; ; If A has changed XOR the A and B bits ... ; But I need to do all the same stuf for when B changes, or I only ; get half as many pulses. ; ; The final logic goes like this - ; Did A change state? (If not, go to B change) ; Yes, then ... ; ; IF A=B, CCW or DOWN step, else, ; IF A<>B, CW or UP step ; ; B changed state, then ... ; ; IF A=B, CW or UP step, else ; IF A<>B, CCW or DOWN step ; ; Neither changed state, exit with no action ... ; ; ; in temp, pinf ; temp gets new value in temp1, gpior0 ; temp1 gets stored value ; Note that it was important to mask off all but bits 4&5 since ; I don't know the state of the other PORTF bits (before saving the ; state in gpior0) andi temp, 0b00110000 ; keep bits 4 & 5 (A & B) out gpior0, temp ; store new value, just <5&4> andi temp1, 0b00110000 ; do same to stored value eor temp1, temp ; if same, result will be 0 breq webedun ; neither changed so exit ; now see which changed ... ; below is for when A changed .. andi temp1, 0b00100000 ; check A, if SET, it changed breq it_was_b ; A changed, check for A = B in temp1, gpior0 ; retrieve new A & B values mov temp, temp1 ; same in temp and temp1 andi temp1, 0b00100000 ; mask to keep B (bit 5) only in temp1 andi temp, 0b00010000 ; mask to keep A only in temp clc ; clear carry ror temp1 ; move bit 5 to bit 4 (roll right) eor temp1, temp ; 1 means NE, 0 means EQUAL breq go_down go_up: sbi gpior0,0 ; set bit 0 to signal up rjmp tune ; below is for when B changed ... it_was_b: ; B changed, check for A = B in temp1, gpior0 ; retrieve new A & B values mov temp, temp1 ; same in temp and temp1 andi temp1, 0b00100000 ; mask to keep B (bit 5) only in temp1 andi temp, 0b00010000 ; mask to keep A only in temp clc ; clear carry ror temp1 ; move bit 5 to bit 4 (roll right) eor temp1, temp ; 1 means NE, 0 means EQUAL breq go_up go_down: sbi gpior0,1 ; set bit 1 to signal down rjmp tune webedun: rjmp wait ;run the loop agian ;straight key mode switch scan wait3: sbis pine,4 ;check other paddle input rjmp t_r rjmp wait2 ;bypass paddle check ;rit routines rit: sbrc flags,3 ;check in rit was already enabled rjmp xrit ;jump if so sbrc flags,2 ;check of xit was alrady enabled rjmp xrit ;jump if so ldi temp,$1b ;write R into lcd charater 6 location sts chrn6,temp sbr flags,$08 ;set rit mode flag (bit 3) ldi zl,low(fbin) ;store current binary tx frequency data ldi zh,high(fbin) ldi yl,low(ritr) ;store into sram labled ritr ldi yh,high(ritr) rcall ram2ram ;move the data rcall lcdwr rjmp wait1 ;go back and wait for switches ;XIT mode setup xrit: ldi zl,low(ritr) ;restore saved tx freq data ldi zh,high(ritr) ldi yl,low(fbin) ldi yh,high(fbin) rcall ram2ram sbrc flags,2 ;check for rit mode [XIT!] rjmp xxit ;jump if in xit mode cbr flags,$08 ;clear rit mode flag rcall off_a sbr flags,$04 ;set xit mode flag ldi temp,$1d sts chrn6,temp ;write T into LCD character 6 rcall lcdwr rjmp wait1 ;go wait for switches ;exit the rit/xit mode xxit: cbr flags,$04 ;clear xit flag rcall off_a rjmp wait1 ;go wait for switches ;initilize the working registers with current bin freq and tuning step data tune: lds r8,fstep lds r9,fstep+1 lds r10,fstep+2 clr r11 lds r12,fbin lds r13,fbin+1 lds r14,fbin+2 lds r15,fbin+3 ; remember: 6 is UP, 7 is DOWN sbis pinb,7 ; desperate attempt to fix tune down rjmp tndn sbis pinb,6 ; check for tune up or down. rjmp tnup ; go if b6 clear, or STICK UP ; if no joystick operated, call must have ; come from encoder ... ; sbic gpior0, 1 ; b1 set -> dn via encoder in process ; rjmp tndn sbic gpior0, 0 ; bit 0 set means UP via encoder in process rjmp tnup ;this decrements the DDS transmit frequency phase word and bcd display tndn: cbi gpior0, 1 ;clear down flag from encoder rcall binsub4 ;calculate new binary freq word rcall off_b ;go calcultate the rx LO frequency sbic pinb,7 rjmp wait1 ;switch open, go back to debounce sbrc flags,1 ;check for rapid tune mode enabled rjmp tunedly ;tune again if so clr dlycnt tdwj: sbic pinb,7 rjmp wait1 ;go back to switch scan / debounce cpi dlycnt,7 ;switch wait delay brne tdwj ;loop if switch still closed sbr flags,$02 ;set 1 bit in flags if switch still closed after 1 second rjmp tune ;this increments the DDS transmit frequency phase word and bcd display tnup: cbi gpior0, 0 ; clear UP flag from encoder rcall binadd4 rcall off_b ;go calcultate the rx LO frequency sbic pinb,6 rjmp wait1 sbrc flags,1 ;check for rapid tune mode enabled rjmp tunedly ;tune again if so clr dlycnt tuwj: sbic pinb,6 rjmp wait1 ;go back to switch scan cpi dlycnt,7 ;switch wait delay brne tuwj ;loop if switch still closed sbr flags,$02 ;set 1 bit in flags if switch still closed after 1 second rjmp tune ;tune again tunedly: clr dlycnt ;fast tune delay twat: cpi dlycnt,1 brne twat rjmp tune off_b: sts fbin,r12 ;store the new operating freq sts fbin+1,r13 sts fbin+2,r14 sts fbin+3,r15 off_a: rcall bin2bcd ;convert freq in bin to bcd rcall calpwd ;calculate dds phase word offset: lds r8,foffset ;load IF offset constant lds r9,foffset+1 lds r10,foffset+2 lds r11,foffset+3 lds r12,ftword ; load Tx phase word lds r13,ftword+1 lds r14,ftword+2 lds r15,ftword+3 rcall binadd4 ;this time add offset to Tx frequency no_off: sts frcv,r12 sts frcv+1,r13 sts frcv+2,r14 sts frcv+3,r15 rcall fout ;up date DDS with new frequency rcall lcdwr ;up date LCD with new frequency ret ;increment frequency tuning rate step step: lds temp,fsk ;get current tuning rate pointer dec temp ;decrement it by one cpi temp,$ff ;check for less than zero brne tnstp ;jump if zero or greater ldi temp,$03 ;load with top count if less than zero tnstp: sts fsk,temp ;store back the new rate pointer value lsl temp ;shift it three times to multiply by 8 lsl temp adjadr: ldi ZH,high(f_table*2) ;initilize flash memory pointer to top of table ldi ZL,low(f_table*2) adj2: add Zl,temp ;add the pointer table offset clr temp adc zh,temp ;add with carry in case of memory boundry ldi YL,low(fstep) ;init Y-pointer to where binary rate data goes in sram ldi yh,high(fstep) ldi temp,4 rcall flash2ram rcall beep ;make a beep rjmp wait1 ;go wait for switches ;100 Mhz values F_TABLE: ;************************************* ;binary values of DDS tuning steps need to be ;recalculated if reference freqency is changed ;************************************** ;10Hz .db $0a,$00 ;binary .db $00,$00 ;100hz .db $64,$00 .db $00,$00 ;1000hz .db $e8,$03 .db $00,$00 ;10Khz .db $10,$27 .db $00,$00 ;100Khz ; .db $a0,$86 ; .db $01,$00 flash2ram: lpm r0,z+ ;get word in flash memory and increment z pointer st Y+,r0 ;store in SRAM and increment Y-pointer dec temp ;decrement counter brne flash2ram ;if not end of table, loop more ret ram2ram:ldi temp,4 ;set up counter to move 4 bytes ramloop:ld temp1,Z+ ;get data pointed to by Z st Y+,temp1 ;store data to address pointed to by Y dec temp ;decrement counter brne ramloop ;if not done, loop more ret binadd4: add r12,r8 ;add these registers adc r13,r9 adc r14,r10 adc r15,r11 ret binsub4: sub r12,r8 ;subtract these registers sbc r13,r9 sbc r14,r10 sbc r15,r11 ret ;set up indirect pointers for transmit frequency txfrq: ldi yl,low(ftword) ldi yh,high(ftword) sbrs flags,3 ;check for RIT rjmp shout ldi yl,low(ritr) ldi yh,high(ritr) rjmp shout ;go to the dds output routine ;set up indirect pointers for receiver frequency fout: ldi yl,low(frcv) ldi yh,high(frcv) sbrs flags,2 ;check for XIT rjmp shout ;go to the dds output routine ldi yl,low(srcv) ldi yh,high(srcv) ;shift out the DDS data with Serial Periferial Interface, ;4 bytes of data and 1 byte of zeros, LSD first shout: ldi temp,4 ;set up counter to send 4 bytes mov cnt1,temp ;load actual counter cbi portb,ddsen ;clear the DDS enable pin spdat: ld temp,y+ ;load the data into temp register out spdr,temp ;output data to SPI data register spwait: in temp1,spsr sbrs temp1,7 ;check busy flag rjmp spwait ;wait till done dec cnt1 ;decrement counter brne spdat ;branch for more data if not done ldi temp,$01 ; assume 9851 mode, enbale X6 pll sbrc flags,0 ; flags[0] CLEAR means 9851 mode ldi temp,0 ; change control byte to 0 for 9850 if flag SET out spdr,temp ;send out zeros spwt2: in temp1,spsr sbrs temp1,7 rjmp spwt2 ;wait until done sbi portb,ddsen ;set the dds enable pin to load data ret chbands: sbis pinb,6 ;wait for up switch closeur rjmp chbands sbis pinb,7 ;wait for down switch closeur rjmp chbands chba: sbis pinb,6 ;check which switch is closed rjmp bd0 ;go increment the band pointer sbis pinb,7 rjmp bddn ;go decrement the band pointer sbis pinb,4 ;check for load the selected band enter switch rjmp bd1 ;go load the new band data rjmp chba ;keep looping bddn: lds temp,bndp dec temp brcc bd9 ldi temp,$09 rjmp bd9 bd0: lds temp,bndp ;load the band pointer inc temp ;increment the pointer cpi temp,$0a ;check for top of pointer exceeded brne bd9 ;branch if okay clr temp ;reset pointer to zero if not bd9: sts bndp,temp ;store back the pointer ldi zh,high(bm0*2) ldi zl,low(bm0*2) add zl,temp clr temp adc zh,temp lpm sts bndigit,r0 rcall bnlcd clr dlycnt ldbj: sbrs dlycnt,1 rjmp ldbj brts bd1 rjmp chbands bm0: .db $16,$80 .db $40,$30 .db $20,$17 .db $15,$12 .db $10,$06 bd1: lds temp,bndp lsl temp ;multiply pointer by 2 lsl temp ;multiply pointer by 2 bd3: ldi ZH,high(ld160*2) ;load Z-pointer with top of table address ldi ZL,low(ld160*2) ;init Z-pointer add Zl,temp ;add the table offset clr temp adc zh,temp ;correct for carry in low byte ldi yL,low(fbin) ;init Y-pointer, for where 1st set of data is to go ldi yh,high(fbin) ;frequency in binary ldi temp,4 ;number of bytes to load rcall flash2ram ;get the data from program flash clt ldband: rcall beep ;make a beep and return rcall off_a ;go to offset routine and return rjmp wait1 ;go to switch scan ;band data ;160 meters ld160: .db $a0,$61 .db $1c,$00 ;80 meters ld80: .db $40,$52 .db $36,$00 ;40 meters ld40: .db $00,$6c .db $6b,$00 ;30 meters ld30: .db $70,$63 .db $9a,$00 ;20 meters ld20: .db $e0,$89 .db $d6,$00 ;17 meters ld17: .db $c0,$08 .db $1d,$01 ;15 meters ld15: .db $a0,$59 .db $41,$01 ;12 meters ld12: .db $90,$ca .db $7b,$01 ;10 meters ld10: .db $60,$29 ;binary .db $ac,$01 ;6 meters ld06: .db $c0,$32 .db $0a,$03 ;staight key transmit mode routine t_r: sbi portf,2 ;activate mute rcall txfrq ;output transmit frequecny sbi porte,6 ;key transmitter sbr flags,$10 ;turn on side tone bit 4 trwait: sbis pine,4 ;wait for key up rjmp trwait trd1: cbi porte,6 ;un key transmitter cbr flags,$10 ;turn off sidetone ldi temp1,7 ; 5 ms delay loop ser temp ;wait for transmitter to decay trdly: dec temp ; brne trdly ; dec temp1 ; brne trdly ;end of delay loop rcall fout ;switch back to receive frequency cbi portf,2 ;un mute receiver rjmp wait ;go wait for switches ;paddle routine padin: sbi portf,2 ;mute reciever rcall txfrq ;switch to transmit frrequency sbi porte,6 ;key transmitter pdin: mov kcnst,cdak ;load keyer time contant into timer register clr dotcnt ;clear the dot counter sbr flags,$10 ;start the side tone sbrc flags,5 ;check for dash flag rjmp dash ;jump if set sbrc flags,6 ;check for dot flag rjmp dot ;jump if set sbis pine,4 ;check if dash paddle closed rjmp dot ;jump to dot if not dash: cbr flags,$20 ;clr dash flag (bit5) dash1: cpi dotcnt,2 brne dash1 ;wait for dot counter to equal 2 dash2: sbis pine,4 ;check to see if dot paddle closed sbr flags,$40 ;set dot flag (bit6) if dot paddle closed cpi dotcnt,9 ;keep checking for dot paddle until end of dash brne dash2 space: clr dotcnt ;clear the dot counter cbr flags,$10 ;turn off the sidetone cbi porte,6 ;un key transmitter ldi temp1,7 ;5ms delay loop to wait for transmitter to decay ser temp ; spwt: dec temp ; brne spwt ; dec temp1 ; brne spwt ;end of delay loop rcall fout ;set receive frequency cbi portf,2 ;un mute receiver spl1: cpi dotcnt,3 ;insert one dot inter element space brne spl1 ; sbrc flags,5 ;check for dash or dot paddle flag set rjmp padin sbrc flags,6 rjmp padin rjmp wait ;go back and wait for switches dot: cbr flags,$40 ;clear the dot flag dot1: cpi dotcnt,$01 ;wait for 1/3 dot time brne dot1 dot2: sbis pine,5 ;check for dash paddle in remaining time sbr flags,$20 ;set flag if dash closed cpi dotcnt,3 brne dot2 ;loop till end of dot time rjmp space ;go to space ;sound a beep from sidetone beep: clr dly clr dlycnt sbi portf,2 ;mute the receiver sbr flags,$10 ;turn on the sidetone bejm: cpi dlycnt,1 brne bejm ;wait for one delay count cbr flags,$10 ;turn off the side tone cbi portf,2 ;un mute the receiver ret ;return ;key transmitter with paddle for tune up tun: sbis pine,5 rjmp tgltx sbis pinb,4 rjmp kfext rjmp tun tgltx: sbi portf,2 ;mute the receiver rcall txfrq ;switch to transmit frequency sbi porte,6 ;key the tranmsitter sbr flags,$10 ;turn on the side tone trwat: sbic pine,4 ;wait for the dash paddle to open rjmp trwat cbi porte,6 ;un key the transmitter ldi temp1,8 ;5 ms timed delay loop ser temp ;allows transmitter to decay before trdl: dec temp ;changing frequency brne trdl dec temp1 brne trdl ;end of delay loop cbr flags,$10 ;turn off the side tone rcall fout ;restore reveiver frequency cbi portf,2 ;un mute the receiver rjmp tun ; function button routines kfunc: sbrc flags,7 ;check for straight key mode rjmp clw ;jump over code speed function if in straight key mode clr dlycnt ;clear the delay counter ldi temp,$0c ;initilize the character locations for code speed display sts chrn6,temp ;load a "C" into character 6 ldi temp,$1c sts chrn5,temp ;load a "S" into character 5 lds temp,csdigit ;get the bcd code speed digit swap temp ;swap the upper nibble into the lower cbr temp,$f0 ;clear the upper mibble sts chrn4,temp ;store into character 4 lds temp,csdigit ;get the bcd digit again cbr temp,$f0 ;clear the upper nibble sts chrn3,temp ;store into character 3 ldi temp,$24 ;store a blank into character 2 and 1 sts chrn2,temp sts chrn1,temp rcall flcdwr ;display the function on lcd kfw10: sbic pine,2 ;switch released" rjmp speed ;jump to speed if so cpi dlycnt,5 ;time delay brne kfw10 ;jump back if not time out yet ldi temp,$1d ;time out load "T" into character 6 sts chrn6,temp ldi temp,$1e sts chrn5,temp ;load "U" ldi temp,$17 sts chrn4,temp ;load "N" ldi temp,$0e sts chrn3,temp ;load "E" rcall flcdwr ;up date lcd display clr dlycnt kfw11: sbic pine,2 ;wait for switch to release rjmp tun cpi dlycnt,5 brne kfw11 clw: rcall bnlcd ;jump to band LCD routine on time out clr dlycnt kfwt9: sbic pine,2 ;check switch to see if still closed rjmp chbands ;jump to change band routine if open cpi dlycnt,20 ;wait for this delay time brne kfwt9 ;delay loop ldi temp,$0c ;switch still closed, set up LCD characters for cal mode sts chrn6,temp ;load "C" into character 6 ldi temp,$0a sts chrn5,temp ;load "A" into character 5 ldi temp,$15 sts chrn4,temp ;load "L" inot character 4 ldi temp,$24 sts chrn3,temp ;load blank inot character 3 ldi temp,$1b sts chrn2,temp ;load "R" into character 2 ldi temp,$18 sts chrn1,temp ;load "O" into character 1 rcall flcdwr ;go display the characters on lcd rjmp cali ;go to calibrate routine and wait some more ;exit the fucntion switch routine kfext: rcall lcdwr ;restore the LCD to frequency number rjmp wait1 ;go wait for switches ;display "BAND" and the bcd band digit on the LCD bnlcd: ldi temp,$0b sts chrn6,temp ldi temp,$0a sts chrn5,temp ldi temp,$17 sts chrn4,temp ldi temp,$0d sts chrn3,temp lds temp,bndigit swap temp cbr temp,$f0 sts chrn2,temp lds temp,bndigit cbr temp,$f0 sts chrn1,temp rcall flcdwr ret ;change the code speed speed: clr dlycnt spd1: sbis pine,4 ;check for dot paddle closed rjmp cdspdn ;go decement code speed if closed sbis pine,5 ;check for dash paddle closed rjmp cdspup ;go increment code speed if closed sbis pinb,4 ;check for escape (enter) switch closed rjmp kfext ;escape if closed cpi dlycnt,20 ;check for time out brne spd1 ;loop if still time rjmp kfext ;escape on time out cdspdn: lds temp,cdsp ;get the current code speed pointer from sram cpi temp,0 ;see if it is zero breq gtk ;if it is, keep it that way dec temp ;if not zero, decrement it one sts cdsp,temp ;store the speed pointer back into sram rjmp gtk ;go get new code speed values cdspup: lds temp,cdsp ;get current code speed pointer cpi temp,30 ;check for bottom of table breq gtk ;branch if it is inc temp ;if not, increment it one sts cdsp,temp ;store it back to sram gtk: lsl temp ;shift to left to mulitply by 2 to correct table location ldi zh,high(cdtbl*2) ;load top of table address into indirect pointer ldi zl,low(cdtbl*2) add zl,temp ;add the table offset to address pointer clr temp adc zh,temp ;add carry to high byte of pointer lpm cdak,z+ ;get the data from flash memory table, store in code speed sram location lpm temp,z ;get the bcd digit for the code speed mov kcnst,cdak ;move the new code speed into timer count register sts csdigit,temp ;move the code bcd digit to sram swap temp ;swap nibbles to put the MSD into the lower nibble cbr temp,$f0 ;clear the upper nibble sts chrn4,temp ;store the MSD into LCD character 4 lds temp,csdigit ;get the speed bcd mumber agian cbr temp,$f0 ;clear the upper nibble for LSD sts chrn3,temp ;store this into LCD character 3 location rcall flcdwr ;go display the speed rcall beep ;sound a beep clr dly ;add a little delay before going back clr dlycnt ssspp: cpi dlycnt,1 brne ssspp rjmp speed ;code speed and bcd digit look up table cdtbl: .db $65,$05 .db $54,$06 .db $48,$07 .db $3f,$08 .db $38,$09 .db $33,$10 .db $2e,$11 .db $2a,$12 .db $27,$13 .db $24,$14 .db $22,$15 .db $20,$16 .db $1e,$17 .db $1c,$18 .db $1b,$19 .db $19,$20 .db $18,$21 .db $17,$22 .db $16,$23 .db $15,$24 .db $14,$25 .db $14,$26 .db $13,$27 .db $12,$28 .db $11,$29 .db $11,$30 .db $10,$32 .db $0f,$34 .db $0e,$36 .db $0d,$38 .db $0c,$40 ; NRK note ; on initial run of this sub, (frequency is 1,860,000 Hz), ; FBCD0, 1, 2, 3 holds 00 00 86 01 on exit ; each nybble contains one decimal digit ... bin2bcd: ldi temp1,32 clr bcd3 clr bcd2 clr bcd1 clr bcd0 clc lds fbin0,fbin lds fbin1,fbin+1 lds fbin2,fbin+2 lds fbin3,fbin+3 bbcdx_1: lsl fbin0 rol fbin1 rol fbin2 rol fbin3 rol bcd0 rol bcd1 rol bcd2 rol bcd3 dec temp1 brne bbcdx_2 sts fbcd,bcd0 sts fbcd0,bcd1 sts fbcd1,bcd2 sts fbcd2,bcd3 ret bbcdx_2: ldi r30,atbcd3+1 clr zh bbcdx_3: ld temp,-z subi temp,-$03 sbrc temp,3 st z,temp ld temp,z subi temp,-$30 sbrc temp,7 st z,temp cpi zl,atbcd0 brne bbcdx_3 rjmp bbcdx_1 ;calculate the DDS phase word using the formula, Pword = (Frequency)(2*32)/reference osc freq ;frequency is in binary and is multiplied by 2*32 by simply putting 32 zeros to the right of ;frequency number. That 64 bit word is then divided by the bianry reference frequency number ;the result will be found in locations dd0 through dd3. calpwd: cli ;clear the interupts clr dd0 ;clear these registers clr dd1 clr dd2 clr dd3 clr dr0 clr dr1 clr dr2 lds dv0,ref_fre ;load diviser,reference frequency lds dv1,ref_fre+1 lds dv2,ref_fre+2 lds dv3,ref_fre+3 lds dd4,fbin ; load dividend,the output frequency lds dd5,fbin+1 lds dd6,fbin+2 lds dd7,fbin+3 ldi temp,65 ;init loop counter sub dr3,dr3 ;clear upper remander byte and carry d16_1: rol dd0 ;shift left dividend rol dd1 rol dd2 rol dd3 rol dd4 rol dd5 rol dd6 rol dd7 dec temp ;decrement counter brne d16_2 ; branch if not done clr zl clr zh ldi yl,low(ftword) ;store the result ldi yh,high(ftword) rcall ram2ram sei ;re-enable the interupts ret ;return d16_2: rol dr0 ;shift dividend into remainder rol dr1 rol dr2 rol dr3 sub dr0,dv0 ;remainder = remainder - divisor sbc dr1,dv1 ; sbc dr2,dv2 sbc dr3,dv3 brcc d16_3 ;if result negative add dr0,dv0 ; restore remainder adc dr1,dv1 adc dr2,dv2 adc dr3,dv3 clc ; clear carry to be shifted into result rjmp d16_1 ;else d16_3: sec ; set carry to be shifted into result rjmp d16_1 ;calibrate or store IF offset mode wait and set up cali: rcall beep ;sound a beep clr dlycnt calij: sbic pine,2 ;check for switch closed rjmp cccc ;jump to cal ro if open cpi dlycnt,10 ;check delay count brne calij ;wait if no time out yet ldi temp,$1c ;load "S" into char 6 sts chrn6,temp ldi temp,$1d ;load "T" into char 5 sts chrn5,temp ldi temp,$1b ;load "R" into char 4 sts chrn4,temp ldi temp,$24 ;load a blank into char3 sts chrn3,temp ldi temp,$18 ;load "O" into char2 sts chrn2,temp ldi temp,$1c ;load "S" into char1 sts chrn1,temp rcall flcdwr ;go display the characters and return rcall beep clr dlycnt conj: sbic pine,2 rjmp stoff ;jump to the store offset routine cpi dlycnt,10 brne conj ldi temp,$0c ;load "C" sts chrn6,temp ldi temp,$15 ;load "L" sts chrn5,temp ldi temp,$1b ;load "R" sts chrn4,temp ldi temp,$24 ;load "blank" sts chrn3,temp ldi temp,$0e ;load "E" sts chrn2,temp ldi temp,$0e ;load "E" sts chrn1,temp rcall flcdwr ; print above stuff to LCD ; ******** V3 new stuff starts here ; ; below code adds menu choice for AD9850 or AD9851 after the ; CLR EE choice. The LCD will display the chip we will be ; changing TO, not the one currently selected ... rcall beep clr dlycnt time4type: sbic pine,2 ; skip if joystick held LEFT rjmp ewjp` ; if released in time, go to wipe EE routine cpi dlycnt, 10 ; timed out? brne time4type ; after this (timed out) we show next menu choice put1char 'A', 2 put1char 'D', 3 put1char '9', 4 put1char '8', 5 put1char '5', 6 put1char '0', 7 ; tentative ... sbrs flags,0 ; bit set means currently 9850, so menu should rjmp dontsay1 ; say going to AD9851 ... put1char '1', 7 dontsay1: ; Now the menu is up, saying which version we will go to if we press the ; stick IN. And we can cancel by going stick RIGHT clr dlycnt ; prepare to time this choice sbis pinb,4 ; skip next if stick switch not IN rjmp newchip ; stick is IN, make the change sbic pine,3 ; skip next if switch is RIGHT rjmp dontsay1 ; loop until IN or RIGHT rjmp calesc ; I hope this fixes display and stuff ... newchip: ldi temp, 1 ; bit 0 set eor flags, temp ; toggle bit 1 only ldi mrenc, 50 ; tentative assumption new chip is 9850 ... ldi eadr, $10 ; eeprom address of chip type flag byte sbrs flags, 0 ; if flags[0] is set, chip is 9850 ldi mrenc, $ff ; flags[0] not set, chip is 9851 call wreed ; burn flag byte for use on start-up call set_ref_f ; this will fix ref freq with default values only rjmp calesc ; ********** V3 back to old stuff here ewjp: sbis pinb,4 rjmp wipee sbis pine,3 rjmp calesc rjmp ewjp wipee: clr eadr ldi temp,$14 ; *** V3 -- was 09 but now we go to $14 mov cnt1,temp ser mrenc ; ser sets all bits so mrenc = $FF clr temp wipmore: out eearh,temp ; eearh is the high byte (just 1 bit) of the eeprom address rcall wreed dec cnt1 ; we don't clear location 0, but that should be OK brne wipmore jmp ckofs ;initilize reference frequency routine cccc: ldi temp,$10 ;load 10000000 into bcd frequency sram registers sts fbcd+3,temp clr temp sts fbcd+2,temp sts fbcd+1,temp sts fbcd,temp ; ********* V3 - had to add selection of ref freq for the ref freq adjust ; ********* routine too ... ; Note below: $0ABA9500 is equal to 180,000,000 ; ... starting point for AD9851 sbrc flags,0 rjmp get9850ref clr temp sts ref_fre,temp ;load default ref freq ldi temp,$95 sts ref_fre+1,temp ldi temp,$ba sts ref_fre+2,temp ldi temp,$0a sts ref_fre+3,temp rjmp got_right1 ; Note below: $05F5E100 is equal to 100,000,000 ; ... starting point for AD9850 get9850ref: clr temp sts ref_fre,temp ;load default ref freq ldi temp,$E1 sts ref_fre+1,temp ldi temp,$F5 sts ref_fre+2,temp ldi temp,$05 sts ref_fre+3,temp got_right1: ;100 Mhz vlaues for 9850 ; ldi temp,$80 ;load the default reference frequency constant ; sts ref_fre+3,temp ;into tx freqeuncy sram registers ; ldi temp,$96 ; sts ref_fre+2,temp ; ldi temp,$98 ; sts ref_fre+1,temp ; clr temp ; sts ref_fre,temp ; NOTE: $988680 in decimal is 10,000,000 ldi temp,$80 sts fbin,temp ldi temp,$96 sts fbin+1,temp ldi temp,$98 sts fbin+2,temp clr temp sts fbin+3,temp rcall calpwd ;go calculate the phase word and return rcall txfrq ;output the frequency rcall lcdwr ;up date the lcd ;scan switches ctwait: sbis pinb,6 ;check for tune switch rjmp ctune sbis pinb,7 ;check for tune switch rjmp ctune sbis pine,3 ;check for escape switch rjmp calesc sbis pinb,4 ;check for do calibration switch rjmp calabt rjmp ctwait ;keep looping ctune: lds r12,ref_fre ;load working registers with phase word lds r13,ref_fre+1 lds r14,ref_fre+2 lds r15,ref_fre+3 ldi temp,$0a ;load a tuning step to working registers mov r8,temp clr r9 clr r10 clr r11 sbis pinb,7 ;check for up down tune rjmp ctup rcall binsub4 ;go subtract the tuning step from frequency word rjmp ctx1 ;jump around tune up ctup: rcall binadd4 ;go add the tuning step and phase word ctx1: sts ref_fre,r12 ;store the results back in ref freq location sts ref_fre+1,r13 sts ref_fre+2,r14 sts ref_fre+3,r15 rcall calpwd ;go calculate the new frequency phase word rcall txfrq ;up date DDS frequency rcall lcdwr ;up date display clr dly clr dlycnt ctxwt: sbrs dlycnt,0 rjmp ctxwt rjmp ctwait ;go wait for switches ;store the new reference frequency constant calabt: clr temp out eearh,temp ldi yl,low(ref_fre) ldi yh,high(ref_fre) clr eadr ; start of eeprom data for 9851 version sbrc flags,0 ; flag clear is 9851 mode ldi eadr, $0C ; start of eeprom data for 9850 version ldi temp1,4 mrdw: ld mrenc,y+ rcall wreed dec temp1 brne mrdw calext: rjmp bd1 calesc: rcall beep rcall beep rjmp bd1 stoff: sbis pine,3 rjmp soext sbic pinb,4 rjmp stoff stost: ldi zl,low(ftword) ldi zh,high(ftword) ldi yl,low(foffset) ldi yh,high(foffset) rcall ram2ram ldi temp1,$04 ldi yl,low(foffset) ldi yh,high(foffset) clr temp out eearh,temp ldi eadr,$04 ; eeprom start for 9851 version IF offset sbrc flags,0 ; bit 0 set means 9850 ldi eadr, $11 ; eeprom start for 9850 version IF offset stoj: ld mrenc,y+ rcall wreed dec temp1 brne stoj soext: rjmp bd1 ;this routine uses character data stored in individual bytes (generally letters) ;finds the segment data for that character and moves the character data to ;lcd memory for display flcdwr: ldi xl,$08 clr xh ldi yl,low(lcddr0) ldi yh,high(lcddr0) lds temp,chrn5 rcall gseg lds temp,chrn6 rcall gseg rcall cmseg ldi xl,$08 ldi yl,low(lcddr1) ldi yh,high(lcddr1) lds temp,chrn3 rcall gseg lds temp,chrn4 rcall gseg rcall cmseg ldi xl,$08 ldi yl,low(lcddr2) ldi yh,high(lcddr2) lds temp,chrn1 rcall gseg lds temp,chrn2 rcall gseg rcall cmseg ret ;this routine un-packs the bcd frequency digits ;finds the segment data for each digit and moves the segements into ;the lcd segement memory lcdwr: ldi xl,$08 clr xh ldi yl,low(lcddr0) ldi yh,high(lcddr0) lds temp,fbcd1 cbr temp,$f0 rcall gseg sbrc flags,2 rjmp rit_d sbrc flags,3 rjmp rit_d lds temp,fbcd1 swap temp cbr temp,$f0 l_jmp: rcall gseg rcall cmseg ldi xl,$08 ldi yl,low(lcddr1) ldi yh,high(lcddr1) lds temp,fbcd0 cbr temp,$f0 rcall gseg lds temp,fbcd0 swap temp cbr temp,$f0 rcall gseg rcall cmseg ldi xl,$08 ldi yl,low(lcddr2) ldi yh,high(lcddr2) lds temp,fbcd cbr temp,$f0 rcall gseg lds temp,fbcd swap temp cbr temp,$f0 rcall gseg rcall cmseg ret rit_d: lds temp,chrn6 rjmp l_jmp ;this routine combines segement data into one packed byte ;and moves it to the lcd segement registers in extended I/O sram cmseg: swap r8 add r8,r12 st y,r8 swap r9 add r9,r13 std y+5,r9 swap r10 add r10,r14 std y+10,r10 swap r11 add r11,r15 std y+15,r11 ret ;this routine gets the segment data for the LCD from a look up table ;and puts the four bytes into working registers. ;a high will turn on the segment. ;segement data is in this order: ;bit number chararacter segments arranged like this: ;76543210 a (top bar) ;0000k--a f h j k b (f- top side bar, h- left diaginal(center to top left corner),j- vertical center,k- right diginal(cneter to top right corner), b- right top side bar) ;0000jfhb gl (g- left center, l- right center) ;0000legc e p n m c (e- left side bar,p- left diaginal (center to bottom left),n- vertical center, m- right digainal(center to bottom right corner), c- bottom right side bar ;0000mpnd d (bottom bar) gseg: ldi zl,low(2*segtable) ldi zh,high(2*segtable) lsl temp lsl temp add zl,temp clr temp adc zh,temp lpm temp,z+ st x+,temp lpm temp,z+ st x+,temp lpm temp,z+ st x+,temp lpm temp,z st x+,temp ret segtable: .db $09,$05 ;0 $00 .db $05,$05 .db $08,$01 ;1 $01 .db $01,$00 .db $01,$01 ;2 $02 .db $0e,$01 .db $01,$01 ;3 $03 .db $0b,$01 .db $00,$05 ;4 $04 .db $0b,$00 .db $01,$04 ;5 $05 .db $0b,$01 .db $01,$04 ;6 $06 .db $0f,$01 .db $01,$01 ;7 $07 .db $01,$00 .db $01,$05 ;8 $08 .db $0f,$01 .db $01,$05 ;9 $09 .db $0b,$00 .db $01,$05 ;A $0a .db $0f,$00 .db $01,$09 ;B $0b .db $09,$03 .db $01,$04 ;C $0c .db $04,$01 .db $01,$09 ;D $0d .db $01,$03 .db $01,$04 ;E $0e .db $0e,$01 .db $01,$04 ;F $0f .db $0e,$00 .db $01,$04 ;G $10 .db $0d,$01 .db $00,$05 ;H $11 .db $0f,$00 .db $00,$08 ;I $12 .db $00,$02 .db $00,$01 ;J $13 .db $05,$01 .db $08,$04 ;K $14 .db $06,$08 .db $00,$04 ;L $15 .db $04,$01 .db $08,$07 ;M $16 .db $05,$00 .db $00,$07 ;N $17 .db $05,$08 .db $01,$05 ;O $18 .db $05,$01 .db $01,$05 ;P $19 .db $0e,$00 .db $01,$05 ;Q $1a .db $05,$09 .db $01,$05 ;R $1b .db $0e,$08 .db $01,$02 ;S $1c .db $00,$09 .db $01,$08 ;T $1d .db $00,$02 .db $00,$05 ;U $1e .db $05,$01 .db $08,$04 ;V $1f .db $04,$04 .db $00,$05 ;W $20 .db $05,$0c .db $08,$02 ;X $21 .db $00,$0c .db $08,$02 ;Y $22 .db $00,$02 .db $09,$00 ;Z $23 .db $00,$05 .db $00,$00 ;blank $24 .db $00,$00 .db $00,$08 ;+ $25 .db $0a,$02 .db $00,$00 ;- $26 .db $0a,$00 wreed: cli out EEARL,eadr ;output address out EEDR,mrenc ;output data sbi eecr,eemwe sbi EECR,EEWE ;set EEPROM Write strobe wre1: sbic EECR,EEWE ;if EEWE not clear rjmp wre1 ; wait more inc eadr sei ret rdeed: out EEARL,eadr ;output address sbi EECR,EERE ;set EEPROM Read strobe ;This instruction takes 4 clock cycles since ;it halts the CPU for two clock cycles sbi EECR,EERE ;set EEPROM Read strobe 2nd time ;This instruction takes 4 clock cycles since ;it halts the CPU for two clock cycles in mrenc,EEDR ;get data inc eadr ret ; Routine below checks flags[0] and sets up reference frequency with ; values for 9850 or 9851 as appropriate. First it checks to see if ; there's a valid value stored in eeprom ; ; in eeprom, the value for the 9851 version is in locations $00 thru $03 ; the value for the 9850 version is in locations $0C thru $0F ; Always stored low byte to high byte set_ref_f: ;check for reference osc cal value in eeprom ; below was location ckofs before I moved to subroutine ldi yl,low(ref_fre) ;load lsd address of sram location ldi yh,high(ref_fre) clr temp ;load eeprom location starting at zero out eearh,temp ; high byte of eeprom address clr eadr sbrc flags,0 ; if 9850, start at location $0C ldi eadr, $0C ldi temp1,4 ;load counter mref: call rdeed ;read eeprom and increment eadr ... st y+,mrenc ;store in sram dec temp1 ;dec counter brne mref ;get more if not done lds temp,ref_fre+3 ;get msb cpi temp,$ff ;check for valid data brne got_ref ;branch if okay test1: clr temp ; Below, if flags[0] is SET, use 9850 values ; and if CLEAR, use 9851 values sbrc flags,0 rjmp do_9850 clr temp ; these are the 9851 180 MHz values sts ref_fre,temp ;load default ref freq ldi temp,$95 sts ref_fre+1,temp ldi temp,$ba sts ref_fre+2,temp ldi temp,$0a sts ref_fre+3,temp rjmp got_ref ; skip over 9850 values ;100 Mhz values for 9850 do_9850: sts ref_fre,temp ;load default ref osc binary value ldi temp,$e1 ;if data not okay sts ref_fre+1,temp ldi temp,$f5 sts ref_fre+2,temp ldi temp,$05 sts ref_fre+3,temp got_ref: ret ; ************************************************************************ ; Subroutine to put string 'NICK' to the display using my put1 LCD routine saynick: ; use Macro PUT1CHAR to put NICK at 4, 5, 6, 7 put1char 'N', 4 put1char 'I', 5 put1char 'C', 6 put1char 'K', 7 ret ; ****************** PUT1 ********************************************** ; A routine to put one character to the LCD screen by WA5BDU ; the character goes in temp and the position goes in temp1 ; put1: push eadr ldi tcnst, 4 ; need to put 4 nybbles ; first, load the base of the LCDDRn registers into Z ; note that the addresses are single byte ; clr zh ldi zl, lcddr0 sbrs temp1, 2 ; if bit 2 is clear, digit is 2 or 3 rjmp gotlcdadr inc zl ; will need at least one increment sbrs temp1, 1 ; if bit 1 is clear, digit is 4 or 5 rjmp gotlcdadr inc zl ; 2nd increment for 6 or 7 gotlcdadr: movw X, Z ; save Z base address in X ; Now I have the base LCDDRn so I need to look up the segment ; data, which is 4 nybbles in 4 separate bytes ... ldi zh, HIGH(2*segtable) ; point to base of segtable ldi zl, LOW(2*segtable) cpi temp, 'A' ; alpha or numeric? brmi is_nmbr adiw zl, 40 ; add 40 to word Z if alphabetic mov eadr, temp ; note SUBI requires register r16 -- r31 subi eadr, 'A' ; calc offset from start of alphabetic lsl eadr ; and multiply by 4 lsl eadr add zl, eadr ; add to base address brcc no_ink1 ; skip next if no carry inc zh no_ink1: rjmp lookitup is_nmbr: mov eadr, temp subi eadr, '0' ; get offset for number in table lsl eadr ; times 4 lsl eadr add zl, eadr brcc lookitup inc zh lookitup: movw Y, Z ; save a copy of pointer into segtable ... lpm dd1, Z ; get the 1st low nybble to dd1 movw Z, X ; retrieve address of lcddr- ld eadr, Z ; get current segment data to eadr sbrc temp1, 0 ; skip next if even char (2, 4, 5) rjmp oddchar ; below, even char known (data to lo nybble) andi eadr, 0b11110000 ; mask off bottom nybble rjmp modifynyb oddchar: swap dd1 ; swap nybbles if odd char (3,5,7), put data to high andi eadr, 0b00001111 ; mask off top nybble modifynyb: or eadr, dd1 ; put new high or low nybble to lcddr- st Z, eadr ; OK, that gets 1st nybble of four ; now I need to increment my lcddr- address by 1 and my segtable byte info by 1 ; and do it again ... dec tcnst ; counter for 4 bytes to update breq fin_put1 ; if zero, we're done ; we're *not* done, so I need to increment my pointer into lcddr- by 5 and ; my pointer to segment data for this character by 1 ; ldi eadr, 5 add zl, eadr ; point to next segment data address movw X, Z ; store in X for now movw Z, Y ; get back pointer into segtable adiw zl, 1 ; point to next segment data byte rjmp lookitup fin_put1: pop eadr ret ; *********************************************************************** ;initialize 9850 dds for serial mode init_dds: sbi portb,ddsen ;set enable pin high nop cbi portb,ddsen ;clear enable pin nop sbi portb,clock ;set clock pin high nop cbi portb,clock ;clear clock pin nop sbi portb,ddsen ;toggle enable pin again nop cbi portb,ddsen clr temp ;data to be sent out spi out spdr,temp ;send 8 zero's to clear control word in dds spwt3: in temp1,spsr ;input spi status register sbrs temp1,7 ;check data finished being sent flag rjmp spwt3 ;wait if not done sbi portb,ddsen ;set enable to load data into dds ret ; *********************************************************************** ; ***************** TIMER2 ISR ***************************************** ;timer interupt routine timer2: in r3,sreg ;store status register dec dly ;decrement fine delay counter brne tm3 ;branc if counter not at zero yet inc dlycnt ;increment final delay counter if dly rolls over tm3: dec kcnst ;decrement the code speed constant brne tm1 ;branch if not yet zero inc dotcnt ;increment the dot counter if zero mov kcnst,cdak ;reload code speed constant tm1: out sreg,r3 ;restore status register sbrs flags,4 ;check for side tone enabled reti ;return from interupt if not sbi pinb,5 ;toggle sidetone port pin if so reti ;return from interupt ; ***********************************************************************