| 
									
										
										
										
											2022-12-22 08:39:24 -05:00
										 |  |  | subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,          &
 | 
					
						
							| 
									
										
										
										
											2023-12-22 15:04:28 -05:00
										 |  |  |      ntrperiod,iseq,mycall0,hiscall0,hisgrid,mode_q65,f0,fqso,nkhz_center,  &
 | 
					
						
							|  |  |  |      newdat,nagain,bClickDecode,max_drift,offset,ndepth,datetime,nCFOM,     &
 | 
					
						
							| 
									
										
										
										
											2024-01-16 11:46:36 -05:00
										 |  |  |      ndop00,nhsym,idec)
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2023-01-25 10:07:07 -05:00
										 |  |  | ! This routine provides an interface between QMAP and the Q65 decoder
 | 
					
						
							|  |  |  | ! in WSJT-X.  All arguments are input data obtained from the QMAP GUI.
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  | ! Raw Rx data are available as the 96 kHz complex spectrum ca(MAXFFT1)
 | 
					
						
							| 
									
										
										
										
											2022-12-22 10:06:29 -05:00
										 |  |  | ! in common/cacb.  Decoded messages are sent back to the GUI.
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  | 
 | 
					
						
							|  |  |  |   use q65_decode
 | 
					
						
							| 
									
										
										
										
											2024-01-20 15:02:51 -05:00
										 |  |  |   use wavhdr
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   use timer_module, only: timer
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   parameter (MAXFFT1=5376000)              !56*96000
 | 
					
						
							|  |  |  |   parameter (MAXFFT2=336000)               !56*6000 (downsampled by 1/16)
 | 
					
						
							|  |  |  |   parameter (NMAX=60*12000)
 | 
					
						
							|  |  |  |   parameter (RAD=57.2957795)
 | 
					
						
							| 
									
										
										
										
											2024-01-20 15:02:51 -05:00
										 |  |  |   type(hdr) h
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   integer*2 iwave(60*12000)
 | 
					
						
							| 
									
										
										
										
											2023-08-31 14:29:20 -04:00
										 |  |  |   integer offset
 | 
					
						
							| 
									
										
										
										
											2022-12-22 10:06:29 -05:00
										 |  |  |   complex ca(MAXFFT1)                      !FFT of raw I/Q data from Linrad
 | 
					
						
							| 
									
										
										
										
											2022-12-11 09:30:01 -05:00
										 |  |  |   complex cx(0:MAXFFT2-1),cz(0:MAXFFT2)
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   real*8 fcenter,freq0,freq1
 | 
					
						
							| 
									
										
										
										
											2023-12-22 15:04:28 -05:00
										 |  |  |   logical*1 bClickDecode
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   character*12 mycall0,hiscall0
 | 
					
						
							|  |  |  |   character*12 mycall,hiscall
 | 
					
						
							| 
									
										
										
										
											2022-12-12 15:50:08 -05:00
										 |  |  |   character*6 hisgrid
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   character*4 grid4
 | 
					
						
							| 
									
										
										
										
											2023-12-07 13:00:21 -05:00
										 |  |  |   character*3 csubmode
 | 
					
						
							| 
									
										
										
										
											2024-01-20 15:02:51 -05:00
										 |  |  |   character*17 fname
 | 
					
						
							| 
									
										
										
										
											2024-01-18 16:25:08 -05:00
										 |  |  |   character*64 result,ctmp
 | 
					
						
							| 
									
										
										
										
											2023-12-08 12:06:20 -05:00
										 |  |  |   character*20 datetime,datetime1
 | 
					
						
							| 
									
										
										
										
											2024-03-12 08:47:23 -04:00
										 |  |  |   common/decodes/ndecodes,ncand2,nQDecoderDone,nWDecoderBusy,              &
 | 
					
						
							| 
									
										
										
										
											2024-01-25 14:27:54 -05:00
										 |  |  |        nWTransmitting,kHzRequested,result(50)
 | 
					
						
							| 
									
										
										
										
											2022-12-11 09:30:01 -05:00
										 |  |  |   common/cacb/ca
 | 
					
						
							| 
									
										
										
										
											2024-01-20 15:02:51 -05:00
										 |  |  |   data ifile/0/
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   save
 | 
					
						
							| 
									
										
										
										
											2023-12-01 08:46:40 -05:00
										 |  |  |   
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   if(mycall0(1:1).ne.' ') mycall=mycall0
 | 
					
						
							|  |  |  |   if(hiscall0(1:1).ne.' ') hiscall=hiscall0
 | 
					
						
							|  |  |  |   if(hisgrid(1:4).ne.'    ') grid4=hisgrid(1:4)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2022-12-13 15:27:33 -05:00
										 |  |  | ! Find best frequency from sync_dat, the "orange sync curve".
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   df3=96000.0/32768.0
 | 
					
						
							| 
									
										
										
										
											2022-12-22 08:20:39 -05:00
										 |  |  |   ipk=(1000.0*f0-1.0)/df3
 | 
					
						
							| 
									
										
										
										
											2024-01-22 11:11:53 -05:00
										 |  |  |   if(nagain.ge.2) ipk = nint(1000.0*(fqso-nkhz_center+48.0)/df3)
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   nfft1=MAXFFT1
 | 
					
						
							|  |  |  |   nfft2=MAXFFT2
 | 
					
						
							|  |  |  |   df=96000.0/NFFT1
 | 
					
						
							|  |  |  |   nh=nfft2/2
 | 
					
						
							|  |  |  |   k0=nint((ipk*df3-1000.0)/df)
 | 
					
						
							|  |  |  |   if(k0.lt.nh .or. k0.gt.MAXFFT1-nfft2+1) go to 900
 | 
					
						
							|  |  |  |   fac=1.0/nfft2
 | 
					
						
							| 
									
										
										
										
											2024-01-22 07:12:40 -05:00
										 |  |  |   cx(0:nfft2-1)=fac*ca(k0:k0+nfft2-1)
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2022-12-11 09:30:01 -05:00
										 |  |  | ! Here cx is frequency-domain data around the selected
 | 
					
						
							| 
									
										
										
										
											2024-01-08 18:55:00 -05:00
										 |  |  | ! QSO frequency, taken from the full-length FFT computed in fftbig().
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  | ! Values for fsample, nfft1, nfft2, df, and the downsampled data rate
 | 
					
						
							|  |  |  | ! are as follows:
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | !  fSample  nfft1       df        nfft2  fDownSampled
 | 
					
						
							|  |  |  | !    (Hz)              (Hz)                 (Hz)
 | 
					
						
							|  |  |  | !----------------------------------------------------
 | 
					
						
							|  |  |  | !   96000  5376000  0.017857143  336000   6000.000
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2022-12-11 09:30:01 -05:00
										 |  |  |   cz(0:MAXFFT2-1)=cx
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   cz(MAXFFT2)=0.
 | 
					
						
							|  |  |  | ! Roll off below 500 Hz and above 2500 Hz.
 | 
					
						
							|  |  |  |   ja=nint(500.0/df)
 | 
					
						
							|  |  |  |   jb=nint(2500.0/df)
 | 
					
						
							|  |  |  |   do i=0,ja
 | 
					
						
							|  |  |  |      r=0.5*(1.0+cos(i*3.14159/ja))
 | 
					
						
							|  |  |  |      cz(ja-i)=r*cz(ja-i)
 | 
					
						
							|  |  |  |      cz(jb+i)=r*cz(jb+i)
 | 
					
						
							|  |  |  |   enddo
 | 
					
						
							|  |  |  |  cz(ja+jb+1:)=0.
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | !Transform to time domain (real), fsample=12000 Hz
 | 
					
						
							|  |  |  |   call four2a(cz,2*nfft2,1,1,-1)
 | 
					
						
							|  |  |  |   do i=0,nfft2-1
 | 
					
						
							|  |  |  |      j=nfft2-1-i
 | 
					
						
							|  |  |  |      iwave(2*i+2)=nint(real(cz(j)))       !Note the reversed order!
 | 
					
						
							|  |  |  |      iwave(2*i+1)=nint(aimag(cz(j)))
 | 
					
						
							|  |  |  |   enddo
 | 
					
						
							|  |  |  |   iwave(2*nfft2+1:)=0
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   nsubmode=mode_q65-1
 | 
					
						
							|  |  |  |   nfa=990                   !Tight limits around ipk for the wideband decode
 | 
					
						
							|  |  |  |   nfb=1010
 | 
					
						
							| 
									
										
										
										
											2024-01-20 15:02:51 -05:00
										 |  |  |   if(nagain.ge.1) then      !For nagain>=1, use limits of +/- ntol
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |      nfa=max(100,1000-ntol)
 | 
					
						
							|  |  |  |      nfb=min(2500,1000+ntol)
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  |   nsnr0=-99             !Default snr for no decode
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2023-12-06 14:22:45 -05:00
										 |  |  |   if(iseq.eq.1) iwave(1:360000)=iwave(360001:720000)
 | 
					
						
							| 
									
										
										
										
											2023-12-08 12:06:20 -05:00
										 |  |  | 
 | 
					
						
							|  |  |  |   csubmode(1:2)='60'
 | 
					
						
							|  |  |  |   csubmode(3:3)=char(ichar('A')+nsubmode)
 | 
					
						
							|  |  |  |   nhhmmss=100*nutc
 | 
					
						
							|  |  |  |   nutc1=nutc
 | 
					
						
							|  |  |  |   datetime(12:13)='00'
 | 
					
						
							|  |  |  |   datetime1=datetime
 | 
					
						
							|  |  |  |   if(ntrperiod.eq.30) then
 | 
					
						
							|  |  |  |      csubmode(1:2)='30'
 | 
					
						
							|  |  |  |      nhhmmss=100*nutc + iseq*30
 | 
					
						
							|  |  |  |      nutc1=nhhmmss
 | 
					
						
							|  |  |  |      if(iseq.eq.1) datetime1(12:13)='30'
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2024-01-22 07:12:40 -05:00
										 |  |  |   if(nagain.ge.2) then
 | 
					
						
							|  |  |  |      ifile=ifile+1
 | 
					
						
							|  |  |  |      write(fname,1000) ifile
 | 
					
						
							|  |  |  | 1000 format('000000_',i6.6,'.wav')
 | 
					
						
							|  |  |  |      open(27,file=fname,status='unknown',access='stream')
 | 
					
						
							|  |  |  |      if(nagain.eq.2) then
 | 
					
						
							|  |  |  |         h=default_header(12000,60*12000)
 | 
					
						
							|  |  |  |         ia=1
 | 
					
						
							|  |  |  |         ib=60*12000
 | 
					
						
							|  |  |  |      else if(nagain.eq.3) then
 | 
					
						
							|  |  |  |         h=default_header(12000,30*12000)
 | 
					
						
							|  |  |  |         ia=1
 | 
					
						
							|  |  |  |         ib=30*12000
 | 
					
						
							|  |  |  |      else
 | 
					
						
							|  |  |  |         h=default_header(12000,30*12000)
 | 
					
						
							|  |  |  |         ia=30*12000 + 1
 | 
					
						
							|  |  |  |         ib=60*12000
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							|  |  |  |      write(27) h,iwave(ia:ib)
 | 
					
						
							|  |  |  |      close(27)
 | 
					
						
							|  |  |  |      go to 900
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2024-01-20 15:02:51 -05:00
										 |  |  |   
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  | ! NB: Frequency of ipk is now shifted to 1000 Hz.
 | 
					
						
							| 
									
										
										
										
											2024-01-20 15:02:51 -05:00
										 |  |  |   nagain2=0
 | 
					
						
							| 
									
										
										
										
											2023-12-08 12:06:20 -05:00
										 |  |  |   call map65_mmdec(nutc1,iwave,nqd,ntrperiod,nsubmode,nfa,nfb,1000,ntol,     &
 | 
					
						
							| 
									
										
										
										
											2024-01-20 15:02:51 -05:00
										 |  |  |        newdat,nagain2,max_drift,ndepth,mycall,hiscall,hisgrid)
 | 
					
						
							| 
									
										
										
										
											2023-12-22 15:04:28 -05:00
										 |  |  |   MHz=fcenter
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   freq0=MHz + 0.001d0*ikhz
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   if(nsnr0.gt.-99) then
 | 
					
						
							| 
									
										
										
										
											2023-12-14 13:37:28 -05:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2024-01-16 11:46:36 -05:00
										 |  |  |      do i=1,ndecodes                    !Check for dupes
 | 
					
						
							|  |  |  |         i1=index(result(i)(42:),trim(msg0))
 | 
					
						
							|  |  |  | !          If this is a dupe, don't save it again:
 | 
					
						
							|  |  |  |         if(i1.gt.0 .and. (.not.bClickDecode .or. nhsym.eq.390)) go to 800
 | 
					
						
							|  |  |  |      enddo
 | 
					
						
							| 
									
										
										
										
											2023-12-14 13:37:28 -05:00
										 |  |  |      
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |      nq65df=nint(1000*(0.001*k0*df+nkhz_center-48.0+1.000-1.27046-ikhz))-nfcal
 | 
					
						
							|  |  |  |      nq65df=nq65df + nfreq0 - 1000
 | 
					
						
							|  |  |  |      ikhz1=ikhz
 | 
					
						
							|  |  |  |      ndf=nq65df
 | 
					
						
							|  |  |  |      if(ndf.gt.500) ikhz1=ikhz + (nq65df+500)/1000
 | 
					
						
							|  |  |  |      if(ndf.lt.-500) ikhz1=ikhz + (nq65df-500)/1000
 | 
					
						
							|  |  |  |      ndf=nq65df - 1000*(ikhz1-ikhz)
 | 
					
						
							|  |  |  |      freq1=freq0 + 0.001d0*(ikhz1-ikhz)
 | 
					
						
							| 
									
										
										
										
											2022-12-13 15:27:33 -05:00
										 |  |  |      frx=0.001*k0*df+nkhz_center-48.0+1.0 - 0.001*nfcal
 | 
					
						
							| 
									
										
										
										
											2023-08-29 13:17:20 +02:00
										 |  |  |      fsked=frx - 0.001*ndop00/2.0 - 0.001*offset
 | 
					
						
							| 
									
										
										
										
											2023-12-07 13:00:21 -05:00
										 |  |  |      ctmp=csubmode//'  '//trim(msg0)
 | 
					
						
							| 
									
										
										
										
											2023-12-14 13:37:28 -05:00
										 |  |  |      ndecodes=min(ndecodes+1,50)
 | 
					
						
							| 
									
										
										
										
											2023-12-07 13:00:21 -05:00
										 |  |  |      write(result(ndecodes),1120) nhhmmss,frx,fsked,xdt0,nsnr0,trim(ctmp)
 | 
					
						
							|  |  |  | 1120 format(i6.6,f9.3,f7.1,f7.2,i5,2x,a)
 | 
					
						
							| 
									
										
										
										
											2023-12-08 12:06:20 -05:00
										 |  |  |      write(12,1130) datetime1,trim(result(ndecodes)(7:))
 | 
					
						
							|  |  |  | 1130 format(a13,1x,a)
 | 
					
						
							| 
									
										
										
										
											2022-12-13 15:27:33 -05:00
										 |  |  |      result(ndecodes)=trim(result(ndecodes))//char(0)
 | 
					
						
							| 
									
										
										
										
											2023-12-14 13:37:28 -05:00
										 |  |  | 800  idec=0
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2022-12-13 15:27:33 -05:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2022-12-17 15:08:26 -05:00
										 |  |  | 900 flush(12)
 | 
					
						
							| 
									
										
										
										
											2022-12-04 10:17:02 -05:00
										 |  |  |   return
 | 
					
						
							|  |  |  | end subroutine q65b
 |