WSJT-X/qmap/libqmap/qmapa.f90

88 lines
3.2 KiB
Fortran
Raw Normal View History

subroutine qmapa(dd,ss,savg,newdat,nutc,fcenter,ntol,nfa,nfb, &
2023-08-29 07:17:20 -04:00
mousedf,mousefqso,nagain,nfshift,max_drift,offset,nfcal,mycall, &
hiscall,hisgrid,nfsample,nmode,ndepth,datetime,ndop00,fselected)
2022-12-12 12:22:52 -05:00
2022-12-22 10:06:29 -05:00
! Processes timf2 data received from Linrad to find and decode Q65 signals.
2022-12-12 12:22:52 -05:00
use timer_module, only: timer
type candidate
real :: snr !Relative S/N of sync detection
real :: f !Freq of sync tone, 0 to 96000 Hz
real :: xdt !DT of matching sync pattern, -1.0 to +4.0 s
integer :: ntrperiod !60 for Q65-60x, 30 for Q65-30x
end type candidate
2022-12-22 10:06:29 -05:00
parameter (NFFT=32768) !Size of FFTs done in symspec()
parameter (MAX_CANDIDATES=50)
2022-12-12 12:22:52 -05:00
parameter (MAXMSG=1000) !Size of decoded message list
parameter (NSMAX=60*96000)
complex cx(NSMAX/64) !Data at 1378.125 samples/s
2022-12-22 10:06:29 -05:00
real dd(2,NSMAX) !I/Q data from Linrad
real ss(373,NFFT) !Symbol spectra
2022-12-22 10:06:29 -05:00
real savg(NFFT) !Average spectrum
real*8 fcenter !Center RF frequency, MHz
2022-12-13 15:04:50 -05:00
character mycall*12,hiscall*12,hisgrid*6
2022-12-12 12:22:52 -05:00
type(candidate) :: cand(MAX_CANDIDATES)
character*60 result
character*20 datetime
2022-12-14 16:52:06 -05:00
common/decodes/ndecodes,ncand,nQDecoderDone,nWDecoderBusy, &
nWTransmitting,result(50)
2022-12-12 12:22:52 -05:00
save
tsec0=sec_midn()
2022-12-22 10:06:29 -05:00
if(nagain.eq.1) ndepth=3 !Use full depth for click-to-decode
2022-12-12 12:22:52 -05:00
nkhz_center=nint(1000.0*(fcenter-int(fcenter)))
mfa=nfa-nkhz_center+48
mfb=nfb-nkhz_center+48
mode_q65=nmode/10
nts_q65=2**(mode_q65-1) !Q65 tone separation factor
f0_selected=fselected - nkhz_center + 48.0
2022-12-12 12:22:52 -05:00
call timer('get_cand',0)
! Get a list of decoding candidates
call getcand2(ss,savg,nts_q65,nagain,ntol,f0_selected,cand,ncand)
call timer('get_cand',1)
2022-12-12 12:22:52 -05:00
nwrite_q65=0
df=96000.0/NFFT !df = 96000/NFFT = 2.930 Hz
ftol=0.010 !Frequency tolerance (kHz)
2022-12-22 10:06:29 -05:00
foffset=0.001*(1270 + nfcal) !Offset from sync tone, plus CAL
2022-12-12 12:22:52 -05:00
fqso=mousefqso + foffset - 0.5*(nfa+nfb) + nfshift !fqso at baseband (khz)
nqd=0
nagain2=0
2022-12-12 12:22:52 -05:00
call timer('filbig ',0)
2022-12-22 10:06:29 -05:00
call filbig(dd,NSMAX,f0,newdat,nfsample,cx,n5) !Do the full-length FFT
2022-12-12 12:22:52 -05:00
call timer('filbig ',1)
2022-12-22 10:06:29 -05:00
do icand=1,ncand !Attempt to decode each candidate
2022-12-13 15:04:50 -05:00
f0=cand(icand)%f
ntrperiod=cand(icand)%ntrperiod
!###
if(icand.gt.1) exit
f0=-31.847 + 117.602
ntrperiod=30
iseq=1
mode_q65=2
!###
freq=f0+nkhz_center-48.0-1.27046
write(*,5001) icand,ntrperiod,iseq,f0,f0+nkhz_center-48.0, &
cand(icand)%xdt,cand(icand)%snr
5001 format('a',3i5,2f10.3,2f8.1)
2022-12-12 12:22:52 -05:00
ikhz=nint(freq)
idec=-1
2022-12-12 12:22:52 -05:00
call timer('q65b ',0)
call q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
ntrperiod,iseq, &
mycall,hiscall,hisgrid,mode_q65,f0,fqso,nkhz_center,newdat, &
2023-08-29 07:17:20 -04:00
nagain2,max_drift,offset,ndepth,datetime,ndop00,idec)
2022-12-12 12:22:52 -05:00
call timer('q65b ',1)
tsec=sec_midn() - tsec0
if(tsec.gt.30.0) exit !Don't start another decode attempt after t=30 s.
2022-12-12 12:22:52 -05:00
enddo ! icand
return
end subroutine qmapa