| 
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 |  |  | subroutine jt65a(dd0,npts,newdat,nutc,nf1,nf2,nfqso,ntol,nsubmode,   &
 | 
					
						
							|  |  |  |      nagain,ndecoded)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | !  Process dd() data to find and decode JT65 signals.
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   parameter (NSZ=3413)
 | 
					
						
							|  |  |  |   parameter (NZMAX=60*12000)
 | 
					
						
							|  |  |  |   parameter (NFFT=8192)
 | 
					
						
							| 
									
										
										
										
											2014-07-31 17:22:51 +00:00
										 |  |  |   real dd0(NZMAX)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   real dd(NZMAX)
 | 
					
						
							|  |  |  |   real*4 ss(322,NSZ)
 | 
					
						
							|  |  |  |   real*4 savg(NSZ)
 | 
					
						
							|  |  |  |   logical done(NSZ)
 | 
					
						
							|  |  |  |   real a(5)
 | 
					
						
							|  |  |  |   character decoded*22
 | 
					
						
							| 
									
										
										
										
											2015-02-13 20:25:49 +00:00
										 |  |  |   common/decstats/num65,numbm,numkv,num9,numfano
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   save
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-07-31 17:22:51 +00:00
										 |  |  |   dd=0.
 | 
					
						
							|  |  |  |   tskip=2.0
 | 
					
						
							|  |  |  |   nskip=12000*tskip
 | 
					
						
							|  |  |  |   dd(1+nskip:npts+nskip)=dd0(1:npts)
 | 
					
						
							|  |  |  |   npts=npts+nskip
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   if(newdat.ne.0) then
 | 
					
						
							|  |  |  |      call timer('symsp65 ',0)
 | 
					
						
							|  |  |  |      call symspec65(dd,npts,ss,nhsym,savg)    !Get normalized symbol spectra
 | 
					
						
							|  |  |  |      call timer('symsp65 ',1)
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   df=12000.0/NFFT                     !df = 12000.0/16384 = 0.732 Hz
 | 
					
						
							| 
									
										
										
										
											2013-07-17 14:18:18 +00:00
										 |  |  |   ftol=16.0                           !Frequency tolerance (Hz)
 | 
					
						
							| 
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 |  |  |   mode65=2**nsubmode
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   done=.false.
 | 
					
						
							| 
									
										
										
										
											2013-07-17 14:18:18 +00:00
										 |  |  |   freq0=-999.
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |   do nqd=1,0,-1
 | 
					
						
							|  |  |  |      if(nqd.eq.1) then                !Quick decode, at fQSO
 | 
					
						
							|  |  |  |         fa=nfqso - ntol
 | 
					
						
							|  |  |  |         fb=nfqso + ntol
 | 
					
						
							|  |  |  |      else                             !Wideband decode at all freqs
 | 
					
						
							| 
									
										
										
										
											2013-08-09 17:22:08 +00:00
										 |  |  |         fa=nf1
 | 
					
						
							|  |  |  |         fb=nf2
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |      endif
 | 
					
						
							|  |  |  |      ia=max(51,nint(fa/df))
 | 
					
						
							|  |  |  |      ib=min(NSZ-51,nint(fb/df))
 | 
					
						
							|  |  |  |      
 | 
					
						
							|  |  |  |      thresh0=1.5
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |      do i=ia,ib                               !Search over freq range
 | 
					
						
							|  |  |  |         freq=i*df
 | 
					
						
							| 
									
										
										
										
											2013-07-17 19:13:36 +00:00
										 |  |  |         if(savg(i).lt.thresh0 .or. done(i)) cycle
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |         call timer('ccf65   ',0)
 | 
					
						
							|  |  |  |         call ccf65(ss(1,i),nhsym,savg(i),sync1,dt,flipk,syncshort,snr2,dt2)
 | 
					
						
							|  |  |  |         call timer('ccf65   ',1)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-17 19:13:36 +00:00
										 |  |  |         ftest=abs(freq-freq0)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |         thresh1=1.0
 | 
					
						
							|  |  |  |         if(nqd.eq.1 .and. ntol.le.100) thresh1=0.
 | 
					
						
							| 
									
										
										
										
											2013-07-17 19:13:36 +00:00
										 |  |  |         if(sync1.lt.thresh1 .or. ftest.lt.ftol) cycle
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |         nflip=nint(flipk)
 | 
					
						
							|  |  |  |         call timer('decod65a',0)
 | 
					
						
							| 
									
										
										
										
											2015-02-05 17:43:43 +00:00
										 |  |  |         call decode65a(dd,npts,newdat,nqd,freq,nflip,mode65,sync2,a,dt,   &
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |              nbmkv,nhist,decoded)
 | 
					
						
							|  |  |  |         call timer('decod65a',1)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-17 19:13:36 +00:00
										 |  |  |         ftest=abs(freq+a(1)-freq0)
 | 
					
						
							|  |  |  |         if(ftest.lt.ftol) cycle
 | 
					
						
							| 
									
										
										
										
											2013-07-17 14:18:18 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |         if(decoded.ne.'                      ') then
 | 
					
						
							|  |  |  |            ndecoded=1
 | 
					
						
							|  |  |  |            nfreq=nint(freq+a(1))
 | 
					
						
							|  |  |  |            ndrift=nint(2.0*a(2))
 | 
					
						
							|  |  |  |            s2db=10.0*log10(sync2) - 32             !### empirical (was 40) ###
 | 
					
						
							|  |  |  |            nsnr=nint(s2db)
 | 
					
						
							|  |  |  |            if(nsnr.lt.-30) nsnr=-30
 | 
					
						
							|  |  |  |            if(nsnr.gt.-1) nsnr=-1
 | 
					
						
							| 
									
										
										
										
											2014-07-31 17:22:51 +00:00
										 |  |  |            dt=dt-tskip
 | 
					
						
							| 
									
										
										
										
											2015-02-13 20:25:49 +00:00
										 |  |  |            if(nbmkv.eq.1) numbm=numbm+1
 | 
					
						
							|  |  |  |            if(nbmkv.eq.2) numkv=numkv+1 
 | 
					
						
							| 
									
										
										
										
											2015-02-04 01:41:26 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-02-06 18:44:45 +00:00
										 |  |  | ! Serialize writes - see also decjt9.f90
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |            !$omp critical(decode_results) 
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |            write(*,1010) nutc,nsnr,dt,nfreq,decoded
 | 
					
						
							| 
									
										
										
										
											2015-02-06 18:44:45 +00:00
										 |  |  | 1010       format(i4.4,i4,f5.1,i5,1x,'#',1x,a22)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |            write(13,1012) nutc,nint(sync1),nsnr,dt,float(nfreq),ndrift,  &
 | 
					
						
							|  |  |  |                 decoded,nbmkv
 | 
					
						
							| 
									
										
										
										
											2015-02-06 18:44:45 +00:00
										 |  |  | 1012       format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a22,' JT65',i4)
 | 
					
						
							| 
									
										
										
										
											2015-02-04 01:41:26 +00:00
										 |  |  |            call flush(6)
 | 
					
						
							| 
									
										
										
										
											2015-02-10 14:04:47 +00:00
										 |  |  |            call flush(13)
 | 
					
						
							| 
									
										
										
										
											2015-02-04 01:41:26 +00:00
										 |  |  |            !$omp end critical(decode_results)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-17 14:18:18 +00:00
										 |  |  |            freq0=freq+a(1)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |            i2=min(NSZ,i+15)                !### ??? ###
 | 
					
						
							|  |  |  |            done(i:i2)=.true.
 | 
					
						
							|  |  |  |         endif
 | 
					
						
							|  |  |  |      enddo
 | 
					
						
							|  |  |  |      if(nagain.eq.1) exit
 | 
					
						
							|  |  |  |   enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   return
 | 
					
						
							|  |  |  | end subroutine jt65a
 |