mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-10-31 04:50:34 -04:00 
			
		
		
		
	Code cleanup and documentation.
This commit is contained in:
		
							parent
							
								
									e0e7ac69fa
								
							
						
					
					
						commit
						88cbc521bd
					
				| @ -43,7 +43,7 @@ subroutine decode0(dd,ss,savg) | |||||||
| 
 | 
 | ||||||
|   call timer('q65wa   ',0) |   call timer('q65wa   ',0) | ||||||
|   call q65wa(dd,ss,savg,newdat,nutc,fcenter,ntol,nfa,nfb,           & |   call q65wa(dd,ss,savg,newdat,nutc,fcenter,ntol,nfa,nfb,           & | ||||||
|        mousedf,mousefqso,nagain,ndecdone,nfshift,max_drift,         & |        mousedf,mousefqso,nagain,nfshift,max_drift,                  & | ||||||
|        nfcal,mycall,hiscall,hisgrid,nfsample,nmode,ndepth,          & |        nfcal,mycall,hiscall,hisgrid,nfsample,nmode,ndepth,          & | ||||||
|        datetime,ndop00) |        datetime,ndop00) | ||||||
|   call timer('q65wa   ',1) |   call timer('q65wa   ',1) | ||||||
|  | |||||||
| @ -102,7 +102,7 @@ subroutine filbig(dd,nmax,f0,newdat,nfsample,c4a,n4) | |||||||
|   enddo |   enddo | ||||||
|   do i=nh+1,nfft2 |   do i=nh+1,nfft2 | ||||||
|      j=i0+i-1-nfft2 |      j=i0+i-1-nfft2 | ||||||
|      if(j.lt.1) j=j+nfft1                  !nfft1 was nfft2 |      if(j.lt.1) j=j+nfft1 | ||||||
|      c4a(i)=rfilt(i)*ca(j) |      c4a(i)=rfilt(i)*ca(j) | ||||||
|   enddo |   enddo | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -1,6 +1,6 @@ | |||||||
| subroutine getcand2(ss,savg0,nts_q65,cand,ncand) | subroutine getcand2(ss,savg0,nts_q65,cand,ncand) | ||||||
| 
 | 
 | ||||||
| !  use wideband_sync | ! Get candidates for Q65 decodes, based on presence of sync tone. | ||||||
|    |    | ||||||
|   type candidate |   type candidate | ||||||
|      real :: snr          !Relative S/N of sync detection |      real :: snr          !Relative S/N of sync detection | ||||||
| @ -8,18 +8,18 @@ subroutine getcand2(ss,savg0,nts_q65,cand,ncand) | |||||||
|      real :: xdt          !DT of matching sync pattern, -1.0 to +4.0 s |      real :: xdt          !DT of matching sync pattern, -1.0 to +4.0 s | ||||||
|   end type candidate |   end type candidate | ||||||
| 
 | 
 | ||||||
|   parameter (NFFT=32768) |   parameter (NFFT=32768)                !FFTs done in symspec() | ||||||
|   parameter (MAX_CANDIDATES=50) |   parameter (MAX_CANDIDATES=50) | ||||||
|   real ss(322,NFFT) |  | ||||||
|   real savg0(NFFT),savg(NFFT) |  | ||||||
|   integer ipk1(1) |  | ||||||
|   logical sync_ok |  | ||||||
|   type(candidate) :: cand(MAX_CANDIDATES) |   type(candidate) :: cand(MAX_CANDIDATES) | ||||||
|  |   real ss(322,NFFT)                     !Symbol spectra | ||||||
|  |   real savg0(NFFT),savg(NFFT)           !Average spectra over whole Rx sequence | ||||||
|  |   integer ipk1(1)                       !Peak index of local portion of spectrum | ||||||
|  |   logical sync_ok                       !True if sync pattern is present | ||||||
|   data nseg/16/,npct/40/ |   data nseg/16/,npct/40/ | ||||||
| 
 | 
 | ||||||
|   savg=savg0 |   savg=savg0                            !Save the original spectrum | ||||||
|   nlen=NFFT/nseg |   nlen=NFFT/nseg | ||||||
|   do iseg=1,nseg |   do iseg=1,nseg                        !Normalize spectrum with nearby baseline | ||||||
|      ja=(iseg-1)*nlen + 1 |      ja=(iseg-1)*nlen + 1 | ||||||
|      jb=ja + nlen - 1 |      jb=ja + nlen - 1 | ||||||
|      call pctile(savg(ja),nlen,npct,base) |      call pctile(savg(ja),nlen,npct,base) | ||||||
| @ -28,22 +28,24 @@ subroutine getcand2(ss,savg0,nts_q65,cand,ncand) | |||||||
|   enddo |   enddo | ||||||
| 
 | 
 | ||||||
|   df=96000.0/NFFT |   df=96000.0/NFFT | ||||||
|   bw=65*nts_q65*1.666666667 |   bw=65*nts_q65*1.666666667             !Bandwidth of Q65 signal | ||||||
|   nbw=bw/df + 1 |   nbw=bw/df + 1                         !Bandwidth in bins | ||||||
|   nb0=2*nts_q65 |   nb0=2*nts_q65                         !Range of peak search, in bins | ||||||
|   smin=1.4 |   smin=1.4                              !First threshold | ||||||
|   nguard=5 |   nguard=5                              !Guard range in bins | ||||||
| 
 | 
 | ||||||
|   j=0 |   j=0 | ||||||
|   do i=1,NFFT-nbw-nguard |   do i=1,NFFT-nbw-nguard          !Look for local peaks in average spectrum | ||||||
|      if(savg(i).lt.smin) cycle |      if(savg(i).lt.smin) cycle | ||||||
|      spk=maxval(savg(i:i+nb0)) |      spk=maxval(savg(i:i+nb0)) | ||||||
|      ipk1=maxloc(savg(i:i+nb0)) |      ipk1=maxloc(savg(i:i+nb0)) | ||||||
|      i0=ipk1(1) + i - 1 |      i0=ipk1(1) + i - 1                         !Index of local peak in savg() | ||||||
|      fpk=0.001*i0*df |      fpk=0.001*i0*df                            !Frequency of peak (kHz) | ||||||
| ! Check to see if sync tone is present. | ! Check to see if sync tone is present. | ||||||
|      call q65_sync(ss,i0,nts_q65,sync_ok,snr_sync,xdt) |      call q65_sync(ss,i0,nts_q65,sync_ok,snr_sync,xdt) | ||||||
|      if(.not.sync_ok) cycle |      if(.not.sync_ok) cycle | ||||||
|  | 
 | ||||||
|  | ! Sync tone is present, we have a candidate for decoding | ||||||
|      j=j+1 |      j=j+1 | ||||||
|      cand(j)%f=fpk |      cand(j)%f=fpk | ||||||
|      cand(j)%xdt=xdt |      cand(j)%xdt=xdt | ||||||
| @ -51,9 +53,9 @@ subroutine getcand2(ss,savg0,nts_q65,cand,ncand) | |||||||
|      ia=min(i,i0-nguard) |      ia=min(i,i0-nguard) | ||||||
|      ib=i0+nbw+nguard |      ib=i0+nbw+nguard | ||||||
|      savg(ia:ib)=0. |      savg(ia:ib)=0. | ||||||
|      if(j.ge.30) exit |      if(j.ge.MAX_CANDIDATES) exit | ||||||
|   enddo |   enddo | ||||||
|   ncand=j |   ncand=j                              !Total number of candidates found | ||||||
| 
 | 
 | ||||||
|   return |   return | ||||||
| end subroutine getcand2 | end subroutine getcand2 | ||||||
|  | |||||||
| @ -1,9 +1,11 @@ | |||||||
| subroutine q65_sync(ss,i0,nts_q65,sync_ok,snr,xdt) | subroutine q65_sync(ss,i0,nts_q65,sync_ok,snr,xdt) | ||||||
| 
 | 
 | ||||||
|  | ! Test for presence of Q65 sync tone | ||||||
|  | 
 | ||||||
|   parameter (NFFT=32768) |   parameter (NFFT=32768) | ||||||
|   parameter (LAGMAX=33) |   parameter (LAGMAX=33) | ||||||
|   real ss(322,NFFT) |   real ss(322,NFFT)                !Symbol spectra | ||||||
|   real ccf(0:LAGMAX) |   real ccf(0:LAGMAX)               !The WSJT "blue curve", peak at DT | ||||||
|   logical sync_ok |   logical sync_ok | ||||||
|   logical first |   logical first | ||||||
|   integer isync(22),ipk(1) |   integer isync(22),ipk(1) | ||||||
| @ -24,12 +26,12 @@ subroutine q65_sync(ss,i0,nts_q65,sync_ok,snr,xdt) | |||||||
| 
 | 
 | ||||||
|   m=nts_q65/2 |   m=nts_q65/2 | ||||||
|   ccf=0. |   ccf=0. | ||||||
|   do lag=0,LAGMAX |   do lag=0,LAGMAX                     !Search over range of DT | ||||||
|      do j=1,22                        !Test for Q65 sync |      do j=1,22                        !Test for Q65 sync | ||||||
|         k=isync(j) + lag |         k=isync(j) + lag | ||||||
| !        ccf=ccf + ss(k,i0) + ss(k+1,i0) + ss(k+2,i0) |  | ||||||
|         ccf(lag)=ccf(lag) + sum(ss(k,i0-m:i0+m)) + sum(ss(k+1,i0-m:i0+m)) & |         ccf(lag)=ccf(lag) + sum(ss(k,i0-m:i0+m)) + sum(ss(k+1,i0-m:i0+m)) & | ||||||
|              + sum(ss(k+2,i0-m:i0+m)) |              + sum(ss(k+2,i0-m:i0+m)) | ||||||
|  | ! Q: Should we use weighted sums, perhaps a Lorentzian peak? | ||||||
|      enddo |      enddo | ||||||
|   enddo |   enddo | ||||||
|   ccfmax=maxval(ccf) |   ccfmax=maxval(ccf) | ||||||
| @ -40,7 +42,7 @@ subroutine q65_sync(ss,i0,nts_q65,sync_ok,snr,xdt) | |||||||
|   xsum=0. |   xsum=0. | ||||||
|   sq=0. |   sq=0. | ||||||
|   nsum=0 |   nsum=0 | ||||||
|   do i=0,lagmax |   do i=0,lagmax                       !Compute ave and rms of "blue curve" | ||||||
|      if(abs(i-lagbest).gt.2) then |      if(abs(i-lagbest).gt.2) then | ||||||
|         xsum=xsum+ccf(i) |         xsum=xsum+ccf(i) | ||||||
|         sq=sq+ccf(i)**2 |         sq=sq+ccf(i)**2 | ||||||
| @ -50,7 +52,7 @@ subroutine q65_sync(ss,i0,nts_q65,sync_ok,snr,xdt) | |||||||
|   ave=xsum/nsum |   ave=xsum/nsum | ||||||
|   rms=sqrt(sq/nsum - ave*ave) |   rms=sqrt(sq/nsum - ave*ave) | ||||||
|   snr=(ccfmax-ave)/rms |   snr=(ccfmax-ave)/rms | ||||||
|   sync_ok=snr.ge.5.0 |   sync_ok=snr.ge.5.0                  !Require snr > 5.0 for sync detection | ||||||
| 
 | 
 | ||||||
|   return |   return | ||||||
| end subroutine q65_sync | end subroutine q65_sync | ||||||
|  | |||||||
| @ -2,13 +2,12 @@ subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,          & | |||||||
|      mycall0,hiscall0,hisgrid,mode_q65,f0,fqso,nkhz_center, newdat,nagain,  & |      mycall0,hiscall0,hisgrid,mode_q65,f0,fqso,nkhz_center, newdat,nagain,  & | ||||||
|      max_drift,ndepth,datetime,ndop00,idec) |      max_drift,ndepth,datetime,ndop00,idec) | ||||||
| 
 | 
 | ||||||
| ! This routine provides an interface between MAP65 and the Q65 decoder | ! This routine provides an interface between Q65W and the Q65 decoder | ||||||
| ! in WSJT-X.  All arguments are input data obtained from the MAP65 GUI. | ! in WSJT-X.  All arguments are input data obtained from the Q65W GUI. | ||||||
| ! Raw Rx data are available as the 96 kHz complex spectrum ca(MAXFFT1) | ! Raw Rx data are available as the 96 kHz complex spectrum ca(MAXFFT1) | ||||||
| ! in common/cacb.  Decoded messages are sent back to the GUI on stdout. | ! in common/cacb.  Decoded messages are sent back to the GUI. | ||||||
| 
 | 
 | ||||||
|   use q65_decode |   use q65_decode | ||||||
| !  use wideband_sync |  | ||||||
|   use timer_module, only: timer |   use timer_module, only: timer | ||||||
| 
 | 
 | ||||||
|   parameter (MAXFFT1=5376000)              !56*96000 |   parameter (MAXFFT1=5376000)              !56*96000 | ||||||
| @ -16,7 +15,7 @@ subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,          & | |||||||
|   parameter (NMAX=60*12000) |   parameter (NMAX=60*12000) | ||||||
|   parameter (RAD=57.2957795) |   parameter (RAD=57.2957795) | ||||||
|   integer*2 iwave(60*12000) |   integer*2 iwave(60*12000) | ||||||
|   complex ca(MAXFFT1)                      !FFTs of raw x,y data |   complex ca(MAXFFT1)                      !FFT of raw I/Q data from Linrad | ||||||
|   complex cx(0:MAXFFT2-1),cz(0:MAXFFT2) |   complex cx(0:MAXFFT2-1),cz(0:MAXFFT2) | ||||||
|   real*8 fcenter,freq0,freq1 |   real*8 fcenter,freq0,freq1 | ||||||
|   character*12 mycall0,hiscall0 |   character*12 mycall0,hiscall0 | ||||||
| @ -64,10 +63,8 @@ subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,          & | |||||||
| !    (Hz)              (Hz)                 (Hz) | !    (Hz)              (Hz)                 (Hz) | ||||||
| !---------------------------------------------------- | !---------------------------------------------------- | ||||||
| !   96000  5376000  0.017857143  336000   6000.000 | !   96000  5376000  0.017857143  336000   6000.000 | ||||||
| !   95238  5120000  0.018601172  322560   5999.994 |  | ||||||
| 
 | 
 | ||||||
|   cz(0:MAXFFT2-1)=cx |   cz(0:MAXFFT2-1)=cx | ||||||
| 
 |  | ||||||
|   cz(MAXFFT2)=0. |   cz(MAXFFT2)=0. | ||||||
| ! Roll off below 500 Hz and above 2500 Hz. | ! Roll off below 500 Hz and above 2500 Hz. | ||||||
|   ja=nint(500.0/df) |   ja=nint(500.0/df) | ||||||
|  | |||||||
| @ -1,11 +1,9 @@ | |||||||
| subroutine q65wa(dd,ss,savg,newdat,nutc,fcenter,ntol,nfa,nfb,         & | subroutine q65wa(dd,ss,savg,newdat,nutc,fcenter,ntol,nfa,nfb,         & | ||||||
|      mousedf,mousefqso,nagain,ndecdone,nfshift,max_drift,             & |      mousedf,mousefqso,nagain,nfshift,max_drift,nfcal,mycall,         & | ||||||
|      nfcal,mycall,hiscall,hisgrid,nfsample,nmode,ndepth,        & |      hiscall,hisgrid,nfsample,nmode,ndepth,datetime,ndop00) | ||||||
|      datetime,ndop00) |  | ||||||
| 
 | 
 | ||||||
| !  Processes timf2 data from Linrad to find and decode JT65 and Q65 signals. | !  Processes timf2 data received from Linrad to find and decode Q65 signals. | ||||||
| 
 | 
 | ||||||
| !  use wideband_sync |  | ||||||
|   use timer_module, only: timer |   use timer_module, only: timer | ||||||
| 
 | 
 | ||||||
|   type candidate |   type candidate | ||||||
| @ -14,27 +12,24 @@ subroutine q65wa(dd,ss,savg,newdat,nutc,fcenter,ntol,nfa,nfb,         & | |||||||
|      real :: xdt          !DT of matching sync pattern, -1.0 to +4.0 s |      real :: xdt          !DT of matching sync pattern, -1.0 to +4.0 s | ||||||
|   end type candidate |   end type candidate | ||||||
| 
 | 
 | ||||||
|   parameter (NFFT=32768) |   parameter (NFFT=32768)             !Size of FFTs done in symspec() | ||||||
|   parameter (MAX_CANDIDATES=50) |   parameter (MAX_CANDIDATES=50) | ||||||
| 
 |  | ||||||
|   parameter (MAXMSG=1000)            !Size of decoded message list |   parameter (MAXMSG=1000)            !Size of decoded message list | ||||||
|   parameter (NSMAX=60*96000) |   parameter (NSMAX=60*96000) | ||||||
|   complex cx(NSMAX/64)               !Data at 1378.125 samples/s |   complex cx(NSMAX/64)               !Data at 1378.125 samples/s | ||||||
|   real dd(2,NSMAX) |   real dd(2,NSMAX)                   !I/Q data from Linrad | ||||||
|   real*4 ss(322,NFFT),savg(NFFT) |   real ss(322,NFFT)                  !Symbol spectra | ||||||
|   real*8 fcenter |   real savg(NFFT)                    !Average spectrum | ||||||
|  |   real*8 fcenter                             !Center RF frequency, MHz | ||||||
|   character mycall*12,hiscall*12,hisgrid*6 |   character mycall*12,hiscall*12,hisgrid*6 | ||||||
|   logical bq65 |  | ||||||
|   logical candec(MAX_CANDIDATES) |  | ||||||
|   type(candidate) :: cand(MAX_CANDIDATES) |   type(candidate) :: cand(MAX_CANDIDATES) | ||||||
|   character*60 result |   character*60 result | ||||||
|   character*20 datetime |   character*20 datetime | ||||||
|   common/decodes/ndecodes,ncand,nQDecoderDone,nWDecoderBusy,              & |   common/decodes/ndecodes,ncand,nQDecoderDone,nWDecoderBusy,              & | ||||||
|        nWTransmitting,result(50) |        nWTransmitting,result(50) | ||||||
|   common/testcom/ifreq |  | ||||||
|   save |   save | ||||||
| 
 | 
 | ||||||
|   if(nagain.eq.1) ndepth=3 |   if(nagain.eq.1) ndepth=3            !Use full depth for click-to-decode | ||||||
|   nkhz_center=nint(1000.0*(fcenter-int(fcenter))) |   nkhz_center=nint(1000.0*(fcenter-int(fcenter))) | ||||||
|   mfa=nfa-nkhz_center+48 |   mfa=nfa-nkhz_center+48 | ||||||
|   mfb=nfb-nkhz_center+48 |   mfb=nfb-nkhz_center+48 | ||||||
| @ -42,40 +37,32 @@ subroutine q65wa(dd,ss,savg,newdat,nutc,fcenter,ntol,nfa,nfb,         & | |||||||
|   nts_q65=2**(mode_q65-1)             !Q65 tone separation factor |   nts_q65=2**(mode_q65-1)             !Q65 tone separation factor | ||||||
| 
 | 
 | ||||||
|   call timer('get_cand',0) |   call timer('get_cand',0) | ||||||
|   call getcand2(ss,savg,nts_q65,cand,ncand) |   call getcand2(ss,savg,nts_q65,cand,ncand) !Get a list of decoding candidates | ||||||
|   call timer('get_cand',1) |   call timer('get_cand',1) | ||||||
| 
 | 
 | ||||||
|   candec=.false. |  | ||||||
|   nwrite_q65=0 |   nwrite_q65=0 | ||||||
|   bq65=mode_q65.gt.0 |  | ||||||
|   df=96000.0/NFFT                     !df = 96000/NFFT = 2.930 Hz |   df=96000.0/NFFT                     !df = 96000/NFFT = 2.930 Hz | ||||||
|   if(nfsample.eq.95238) df=95238.1/NFFT |   if(nfsample.eq.95238) df=95238.1/NFFT | ||||||
|   ftol=0.010                          !Frequency tolerance (kHz) |   ftol=0.010                          !Frequency tolerance (kHz) | ||||||
|   foffset=0.001*(1270 + nfcal)              !Offset from sync tone, plus CAL |   foffset=0.001*(1270 + nfcal)        !Offset from sync tone, plus CAL | ||||||
|   fqso=mousefqso + foffset - 0.5*(nfa+nfb) + nfshift !fqso at baseband (khz) |   fqso=mousefqso + foffset - 0.5*(nfa+nfb) + nfshift !fqso at baseband (khz) | ||||||
|   iloop=0 |  | ||||||
|   nqd=0 |   nqd=0 | ||||||
| 
 | 
 | ||||||
|   call timer('filbig  ',0) |   call timer('filbig  ',0) | ||||||
|   call filbig(dd,NSMAX,f0,newdat,nfsample,cx,n5) |   call filbig(dd,NSMAX,f0,newdat,nfsample,cx,n5) !Do the full-length FFT | ||||||
|   call timer('filbig  ',1) |   call timer('filbig  ',1) | ||||||
| 
 | 
 | ||||||
| ! Do the wideband Q65 decode |   do icand=1,ncand                        !Attempt to decode each candidate | ||||||
|   do icand=1,ncand |  | ||||||
|      f0=cand(icand)%f |      f0=cand(icand)%f | ||||||
|      if(candec(icand)) cycle             !Skip if already decoded |  | ||||||
|      freq=cand(icand)%f+nkhz_center-48.0-1.27046 |      freq=cand(icand)%f+nkhz_center-48.0-1.27046 | ||||||
|      ikhz=nint(freq) |      ikhz=nint(freq) | ||||||
|      idec=-1 |      idec=-1 | ||||||
| 
 |  | ||||||
|      call timer('q65b    ',0) |      call timer('q65b    ',0) | ||||||
|      call q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,       & |      call q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,       & | ||||||
|           mycall,hiscall,hisgrid,mode_q65,f0,fqso,nkhz_center,newdat,   & |           mycall,hiscall,hisgrid,mode_q65,f0,fqso,nkhz_center,newdat,   & | ||||||
|           nagain,max_drift,ndepth,datetime,ndop00,idec) |           nagain,max_drift,ndepth,datetime,ndop00,idec) | ||||||
|      call timer('q65b    ',1) |      call timer('q65b    ',1) | ||||||
|      if(idec.ge.0) candec(icand)=.true. |  | ||||||
|   enddo  ! icand |   enddo  ! icand | ||||||
|   ndecdone=2 |  | ||||||
| 
 | 
 | ||||||
|   return |   return | ||||||
| end subroutine q65wa | end subroutine q65wa | ||||||
|  | |||||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user