mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2025-06-25 14:45:14 -04:00
Merge branch 'map65' of bitbucket.org:k1jt/wsjtx into map65
This commit is contained in:
commit
ee497eecff
@ -1,6 +1,5 @@
|
|||||||
set (libq65_FSRCS
|
set (libq65_FSRCS
|
||||||
# Modules come first:
|
# Modules come first:
|
||||||
wideband_sync.f90
|
|
||||||
|
|
||||||
# Non-module Fortran routines:
|
# Non-module Fortran routines:
|
||||||
astro.f90
|
astro.f90
|
||||||
@ -14,14 +13,16 @@ set (libq65_FSRCS
|
|||||||
four2a.f90
|
four2a.f90
|
||||||
ftninit.f90
|
ftninit.f90
|
||||||
ftnquit.f90
|
ftnquit.f90
|
||||||
q65b.f90
|
|
||||||
geocentric.f90
|
geocentric.f90
|
||||||
|
getcand2.f90
|
||||||
grid2deg.f90
|
grid2deg.f90
|
||||||
indexx.f90
|
indexx.f90
|
||||||
lorentzian.f90
|
lorentzian.f90
|
||||||
moon2.f90
|
moon2.f90
|
||||||
moondop.f90
|
moondop.f90
|
||||||
|
q65b.f90
|
||||||
q65c.f90
|
q65c.f90
|
||||||
|
q65_sync.f90
|
||||||
q65wa.f90
|
q65wa.f90
|
||||||
recvpkt.f90
|
recvpkt.f90
|
||||||
sun.f90
|
sun.f90
|
||||||
|
@ -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
|
||||||
|
|
||||||
|
61
q65w/libq65/getcand2.f90
Normal file
61
q65w/libq65/getcand2.f90
Normal file
@ -0,0 +1,61 @@
|
|||||||
|
subroutine getcand2(ss,savg0,nts_q65,cand,ncand)
|
||||||
|
|
||||||
|
! Get candidates for Q65 decodes, based on presence of sync tone.
|
||||||
|
|
||||||
|
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
|
||||||
|
end type candidate
|
||||||
|
|
||||||
|
parameter (NFFT=32768) !FFTs done in symspec()
|
||||||
|
parameter (MAX_CANDIDATES=50)
|
||||||
|
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/
|
||||||
|
|
||||||
|
savg=savg0 !Save the original spectrum
|
||||||
|
nlen=NFFT/nseg
|
||||||
|
do iseg=1,nseg !Normalize spectrum with nearby baseline
|
||||||
|
ja=(iseg-1)*nlen + 1
|
||||||
|
jb=ja + nlen - 1
|
||||||
|
call pctile(savg(ja),nlen,npct,base)
|
||||||
|
savg(ja:jb)=savg(ja:jb)/(1.015*base)
|
||||||
|
savg0(ja:jb)=savg0(ja:jb)/(1.015*base)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
df=96000.0/NFFT
|
||||||
|
bw=65*nts_q65*1.666666667 !Bandwidth of Q65 signal
|
||||||
|
nbw=bw/df + 1 !Bandwidth in bins
|
||||||
|
nb0=2*nts_q65 !Range of peak search, in bins
|
||||||
|
smin=1.4 !First threshold
|
||||||
|
nguard=5 !Guard range in bins
|
||||||
|
|
||||||
|
j=0
|
||||||
|
do i=1,NFFT-nbw-nguard !Look for local peaks in average spectrum
|
||||||
|
if(savg(i).lt.smin) cycle
|
||||||
|
spk=maxval(savg(i:i+nb0))
|
||||||
|
ipk1=maxloc(savg(i:i+nb0))
|
||||||
|
i0=ipk1(1) + i - 1 !Index of local peak in savg()
|
||||||
|
fpk=0.001*i0*df !Frequency of peak (kHz)
|
||||||
|
! Check to see if sync tone is present.
|
||||||
|
call q65_sync(ss,i0,nts_q65,sync_ok,snr_sync,xdt)
|
||||||
|
if(.not.sync_ok) cycle
|
||||||
|
|
||||||
|
! Sync tone is present, we have a candidate for decoding
|
||||||
|
j=j+1
|
||||||
|
cand(j)%f=fpk
|
||||||
|
cand(j)%xdt=xdt
|
||||||
|
cand(j)%snr=snr_sync
|
||||||
|
ia=min(i,i0-nguard)
|
||||||
|
ib=i0+nbw+nguard
|
||||||
|
savg(ia:ib)=0.
|
||||||
|
if(j.ge.MAX_CANDIDATES) exit
|
||||||
|
enddo
|
||||||
|
ncand=j !Total number of candidates found
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine getcand2
|
58
q65w/libq65/q65_sync.f90
Normal file
58
q65w/libq65/q65_sync.f90
Normal file
@ -0,0 +1,58 @@
|
|||||||
|
subroutine q65_sync(ss,i0,nts_q65,sync_ok,snr,xdt)
|
||||||
|
|
||||||
|
! Test for presence of Q65 sync tone
|
||||||
|
|
||||||
|
parameter (NFFT=32768)
|
||||||
|
parameter (LAGMAX=33)
|
||||||
|
real ss(322,NFFT) !Symbol spectra
|
||||||
|
real ccf(0:LAGMAX) !The WSJT "blue curve", peak at DT
|
||||||
|
logical sync_ok
|
||||||
|
logical first
|
||||||
|
integer isync(22),ipk(1)
|
||||||
|
|
||||||
|
! Q65 sync symbols
|
||||||
|
data isync/1,9,12,13,15,22,23,26,27,33,35,38,46,50,55,60,62,66,69,74,76,85/
|
||||||
|
data first/.true./
|
||||||
|
save first,isync
|
||||||
|
|
||||||
|
tstep=2048.0/11025.0 !0.185760 s: 0.5*tsym_jt65, 0.3096*tsym_q65
|
||||||
|
if(first) then
|
||||||
|
fac=0.6/tstep !3.230
|
||||||
|
do i=1,22 !Expand the Q65 sync stride
|
||||||
|
isync(i)=nint((isync(i)-1)*fac) + 1
|
||||||
|
enddo
|
||||||
|
first=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
m=nts_q65/2
|
||||||
|
ccf=0.
|
||||||
|
do lag=0,LAGMAX !Search over range of DT
|
||||||
|
do j=1,22 !Test for Q65 sync
|
||||||
|
k=isync(j) + lag
|
||||||
|
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))
|
||||||
|
! Q: Should we use weighted sums, perhaps a Lorentzian peak?
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
ccfmax=maxval(ccf)
|
||||||
|
ipk=maxloc(ccf)
|
||||||
|
lagbest=ipk(1)-1
|
||||||
|
xdt=lagbest*tstep - 1.0
|
||||||
|
|
||||||
|
xsum=0.
|
||||||
|
sq=0.
|
||||||
|
nsum=0
|
||||||
|
do i=0,lagmax !Compute ave and rms of "blue curve"
|
||||||
|
if(abs(i-lagbest).gt.2) then
|
||||||
|
xsum=xsum+ccf(i)
|
||||||
|
sq=sq+ccf(i)**2
|
||||||
|
nsum=nsum+1
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
ave=xsum/nsum
|
||||||
|
rms=sqrt(sq/nsum - ave*ave)
|
||||||
|
snr=(ccfmax-ave)/rms
|
||||||
|
sync_ok=snr.ge.5.0 !Require snr > 5.0 for sync detection
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine q65_sync
|
@ -1,25 +1,22 @@
|
|||||||
subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
|
subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
|
||||||
mycall0,hiscall0,hisgrid,mode_q65,f0,fqso,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
|
||||||
parameter (MAXFFT2=336000) !56*6000 (downsampled by 1/16)
|
parameter (MAXFFT2=336000) !56*6000 (downsampled by 1/16)
|
||||||
parameter (NMAX=60*12000)
|
parameter (NMAX=60*12000)
|
||||||
parameter (RAD=57.2957795)
|
parameter (RAD=57.2957795)
|
||||||
! type(hdr) h !Header for the .wav file
|
|
||||||
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)
|
||||||
integer ipk1(1)
|
|
||||||
real*8 fcenter,freq0,freq1
|
real*8 fcenter,freq0,freq1
|
||||||
character*12 mycall0,hiscall0
|
character*12 mycall0,hiscall0
|
||||||
character*12 mycall,hiscall
|
character*12 mycall,hiscall
|
||||||
@ -38,16 +35,7 @@ subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
|
|||||||
|
|
||||||
! Find best frequency from sync_dat, the "orange sync curve".
|
! Find best frequency from sync_dat, the "orange sync curve".
|
||||||
df3=96000.0/32768.0
|
df3=96000.0/32768.0
|
||||||
ifreq=nint((1000.0*f0)/df3)
|
ipk=(1000.0*f0-1.0)/df3
|
||||||
ia=nint(ifreq-ntol/df3)
|
|
||||||
ib=nint(ifreq+ntol/df3)
|
|
||||||
ipk1=maxloc(sync(ia:ib)%ccfmax)
|
|
||||||
ipk=ia+ipk1(1)-1
|
|
||||||
! f_ipk=ipk*df3
|
|
||||||
ipk2=(1000.0*f0-1.0)/df3
|
|
||||||
snr1=sync(ipk)%ccfmax
|
|
||||||
ipk=ipk2 !Substitute new ipk value
|
|
||||||
|
|
||||||
nfft1=MAXFFT1
|
nfft1=MAXFFT1
|
||||||
nfft2=MAXFFT2
|
nfft2=MAXFFT2
|
||||||
df=96000.0/NFFT1
|
df=96000.0/NFFT1
|
||||||
@ -62,8 +50,6 @@ subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
|
|||||||
if(nagain.eq.1) k0=nint((f_mouse-1000.0)/df)
|
if(nagain.eq.1) k0=nint((f_mouse-1000.0)/df)
|
||||||
|
|
||||||
if(k0.lt.nh .or. k0.gt.MAXFFT1-nfft2+1) go to 900
|
if(k0.lt.nh .or. k0.gt.MAXFFT1-nfft2+1) go to 900
|
||||||
if(snr1.lt.1.5) go to 900 !### Threshold needs work? ###
|
|
||||||
|
|
||||||
fac=1.0/nfft2
|
fac=1.0/nfft2
|
||||||
cx(0:nfft2-1)=ca(k0:k0+nfft2-1)
|
cx(0:nfft2-1)=ca(k0:k0+nfft2-1)
|
||||||
cx=fac*cx
|
cx=fac*cx
|
||||||
@ -77,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)
|
||||||
@ -111,7 +95,6 @@ subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
|
|||||||
nsnr0=-99 !Default snr for no decode
|
nsnr0=-99 !Default snr for no decode
|
||||||
|
|
||||||
! NB: Frequency of ipk is now shifted to 1000 Hz.
|
! NB: Frequency of ipk is now shifted to 1000 Hz.
|
||||||
|
|
||||||
call map65_mmdec(nutc,iwave,nqd,nsubmode,nfa,nfb,1000,ntol, &
|
call map65_mmdec(nutc,iwave,nqd,nsubmode,nfa,nfb,1000,ntol, &
|
||||||
newdat,nagain,max_drift,ndepth,mycall,hiscall,hisgrid)
|
newdat,nagain,max_drift,ndepth,mycall,hiscall,hisgrid)
|
||||||
MHz=fcenter
|
MHz=fcenter
|
||||||
@ -134,11 +117,9 @@ subroutine q65b(nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
|
|||||||
write(12,1130) datetime,trim(result(ndecodes)(5:))
|
write(12,1130) datetime,trim(result(ndecodes)(5:))
|
||||||
1130 format(a11,1x,a)
|
1130 format(a11,1x,a)
|
||||||
result(ndecodes)=trim(result(ndecodes))//char(0)
|
result(ndecodes)=trim(result(ndecodes))//char(0)
|
||||||
! print*,'AAA',f_ipk,k0*df,f0,ipk,ipk2,trim(msg0)
|
|
||||||
idec=0
|
idec=0
|
||||||
endif
|
endif
|
||||||
|
|
||||||
900 flush(12)
|
900 flush(12)
|
||||||
|
|
||||||
return
|
return
|
||||||
end subroutine q65b
|
end subroutine q65b
|
||||||
|
@ -1,32 +1,35 @@
|
|||||||
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
|
||||||
|
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
|
||||||
|
end type candidate
|
||||||
|
|
||||||
|
parameter (NFFT=32768) !Size of FFTs done in symspec()
|
||||||
|
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
|
||||||
@ -34,174 +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 get_candidates(ss,savg,nhsym,mfa,mfb,nts_jt65,nts_q65,cand,ncand)
|
call getcand2(ss,savg,nts_q65,cand,ncand) !Get a list of decoding candidates
|
||||||
call getcand2(ss,savg,nts_q65,cand,ncand)
|
|
||||||
call timer('get_cand',1)
|
call timer('get_cand',1)
|
||||||
|
|
||||||
! do i=1,ncand
|
|
||||||
! write(71,3071) i,cand(i)%f,cand(i)%xdt,cand(i)%snr
|
|
||||||
!3071 format(i2,3f10.3)
|
|
||||||
! enddo
|
|
||||||
|
|
||||||
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(cand(icand)%iflip.ne.0) cycle !Do only Q65 candidates here
|
|
||||||
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
|
||||||
|
|
||||||
! print*,'AAA',icand,nutc,nqd,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
|
|
||||||
! mycall,hiscall,hisgrid,mode_q65,f0,fqso,newdat, &
|
|
||||||
! nagain,max_drift,ndop00
|
|
||||||
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,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.
|
|
||||||
|
|
||||||
! write(71,3071) icand,cand(icand)%f,32.0+cand(icand)%f, &
|
|
||||||
! cand(icand)%xdt,cand(icand)%snr,idec,ndecodes
|
|
||||||
!3071 format(i2,4f10.3,2i5)
|
|
||||||
|
|
||||||
enddo ! icand
|
enddo ! icand
|
||||||
ndecdone=2
|
|
||||||
|
|
||||||
return
|
return
|
||||||
end subroutine q65wa
|
end subroutine q65wa
|
||||||
|
|
||||||
subroutine getcand2(ss,savg0,nts_q65,cand,ncand)
|
|
||||||
|
|
||||||
use wideband_sync
|
|
||||||
! parameter(NFFT=32768)
|
|
||||||
real ss(322,NFFT)
|
|
||||||
real savg0(NFFT),savg(NFFT)
|
|
||||||
integer ipk1(1)
|
|
||||||
logical sync_ok
|
|
||||||
type(candidate) :: cand(MAX_CANDIDATES)
|
|
||||||
data nseg/16/,npct/40/
|
|
||||||
|
|
||||||
savg=savg0
|
|
||||||
nlen=NFFT/nseg
|
|
||||||
do iseg=1,nseg
|
|
||||||
ja=(iseg-1)*nlen + 1
|
|
||||||
jb=ja + nlen - 1
|
|
||||||
call pctile(savg(ja),nlen,npct,base)
|
|
||||||
savg(ja:jb)=savg(ja:jb)/(1.015*base)
|
|
||||||
savg0(ja:jb)=savg0(ja:jb)/(1.015*base)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
df=96000.0/NFFT
|
|
||||||
bw=65*nts_q65*1.666666667
|
|
||||||
nbw=bw/df + 1
|
|
||||||
smin=1.4
|
|
||||||
nguard=5
|
|
||||||
|
|
||||||
j=0
|
|
||||||
sync(1:NFFT)%ccfmax=0.
|
|
||||||
|
|
||||||
do i=1,NFFT-2*nbw
|
|
||||||
if(savg(i).lt.smin) cycle
|
|
||||||
spk=maxval(savg(i:i+nbw))
|
|
||||||
ipk1=maxloc(savg(i:i+nbw))
|
|
||||||
i0=ipk1(1) + i - 1
|
|
||||||
fpk=0.001*i0*df
|
|
||||||
! Check to see if sync tone is present.
|
|
||||||
call q65_sync(ss,i0,nts_q65,sync_ok,snr_sync,xdt)
|
|
||||||
if(.not.sync_ok) cycle
|
|
||||||
j=j+1
|
|
||||||
! write(73,3073) j,fpk+32.0-2.270,snr_sync,xdt
|
|
||||||
!3073 format(i3,3f10.3)
|
|
||||||
cand(j)%f=fpk
|
|
||||||
cand(j)%xdt=2.8
|
|
||||||
cand(j)%snr=spk
|
|
||||||
cand(j)%iflip=0
|
|
||||||
sync(i0)%ccfmax=spk
|
|
||||||
ia=min(i,i0-nguard)
|
|
||||||
ib=i0+nbw+nguard
|
|
||||||
savg(ia:ib)=0.
|
|
||||||
if(j.ge.30) exit
|
|
||||||
enddo
|
|
||||||
ncand=j
|
|
||||||
|
|
||||||
! do i=1,NFFT
|
|
||||||
! write(72,3072) i,0.001*i*df+32.0,savg0(i),savg(i),sync(i)%ccfmax
|
|
||||||
!3072 format(i6,f15.6,3f15.3)
|
|
||||||
! enddo
|
|
||||||
|
|
||||||
return
|
|
||||||
end subroutine getcand2
|
|
||||||
|
|
||||||
subroutine q65_sync(ss,i0,nts_q65,sync_ok,snr,xdt)
|
|
||||||
|
|
||||||
parameter (NFFT=32768)
|
|
||||||
parameter (LAGMAX=33)
|
|
||||||
real ss(322,NFFT)
|
|
||||||
real ccf(0:LAGMAX)
|
|
||||||
logical sync_ok
|
|
||||||
logical first
|
|
||||||
integer isync(22),ipk(1)
|
|
||||||
|
|
||||||
! Q65 sync symbols
|
|
||||||
data isync/1,9,12,13,15,22,23,26,27,33,35,38,46,50,55,60,62,66,69,74,76,85/
|
|
||||||
data first/.true./
|
|
||||||
save first,isync
|
|
||||||
|
|
||||||
tstep=2048.0/11025.0 !0.185760 s: 0.5*tsym_jt65, 0.3096*tsym_q65
|
|
||||||
if(first) then
|
|
||||||
fac=0.6/tstep !3.230
|
|
||||||
do i=1,22 !Expand the Q65 sync stride
|
|
||||||
isync(i)=nint((isync(i)-1)*fac) + 1
|
|
||||||
enddo
|
|
||||||
first=.false.
|
|
||||||
endif
|
|
||||||
|
|
||||||
m=nts_q65/2
|
|
||||||
ccf=0.
|
|
||||||
do lag=0,LAGMAX
|
|
||||||
do j=1,22 !Test for Q65 sync
|
|
||||||
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)) &
|
|
||||||
+ sum(ss(k+2,i0-m:i0+m))
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
ccfmax=maxval(ccf)
|
|
||||||
ipk=maxloc(ccf)
|
|
||||||
lagbest=ipk(1)-1
|
|
||||||
xdt=lagbest*tstep - 1.0
|
|
||||||
|
|
||||||
xsum=0.
|
|
||||||
sq=0.
|
|
||||||
nsum=0
|
|
||||||
do i=0,lagmax
|
|
||||||
if(abs(i-lagbest).gt.2) then
|
|
||||||
xsum=xsum+ccf(i)
|
|
||||||
sq=sq+ccf(i)**2
|
|
||||||
nsum=nsum+1
|
|
||||||
endif
|
|
||||||
enddo
|
|
||||||
ave=xsum/nsum
|
|
||||||
rms=sqrt(sq/nsum - ave*ave)
|
|
||||||
snr=(ccfmax-ave)/rms
|
|
||||||
sync_ok=snr.ge.5.0
|
|
||||||
|
|
||||||
return
|
|
||||||
end subroutine q65_sync
|
|
||||||
|
@ -1,57 +0,0 @@
|
|||||||
program synctest
|
|
||||||
|
|
||||||
! Program to test an algorithm for detecting sync signals for both
|
|
||||||
! JT65 and Q65-60x signals and rejecting birdies in MAP65 data.
|
|
||||||
! The important work is done in module wideband_sync.
|
|
||||||
|
|
||||||
use timer_module, only: timer
|
|
||||||
use timer_impl, only: init_timer, fini_timer
|
|
||||||
use wideband_sync
|
|
||||||
|
|
||||||
real ss(4,322,NFFT),savg(4,NFFT)
|
|
||||||
! real candidate(MAX_CANDIDATES,5) !snr1,f0,xdt0,ipol,flip
|
|
||||||
character*8 arg
|
|
||||||
type(candidate) :: cand(MAX_CANDIDATES)
|
|
||||||
|
|
||||||
nargs=iargc()
|
|
||||||
if(nargs.ne.5) then
|
|
||||||
print*,'Usage: synctest iutc nfa nfb nts_jt65 nts_q65'
|
|
||||||
print*,'Example: synctest 1814 23 83 2 1'
|
|
||||||
go to 999
|
|
||||||
endif
|
|
||||||
call getarg(1,arg)
|
|
||||||
read (arg,*) iutc
|
|
||||||
call getarg(2,arg)
|
|
||||||
read (arg,*) nfa
|
|
||||||
call getarg(3,arg)
|
|
||||||
read (arg,*) nfb
|
|
||||||
call getarg(4,arg)
|
|
||||||
read (arg,*) nts_jt65
|
|
||||||
call getarg(5,arg)
|
|
||||||
read (arg,*) nts_q65
|
|
||||||
|
|
||||||
open(50,file='50.a',form='unformatted',status='old')
|
|
||||||
do ifile=1,9999
|
|
||||||
read(50,end=998) nutc,npol,ss(1:npol,:,:),savg(1:npol,:)
|
|
||||||
if(nutc.eq.iutc) exit
|
|
||||||
enddo
|
|
||||||
close(50)
|
|
||||||
|
|
||||||
call init_timer('timer.out')
|
|
||||||
call timer('synctest',0)
|
|
||||||
|
|
||||||
call timer('get_cand',0)
|
|
||||||
call get_candidates(ss,savg,302,.true.,nfa,nfb,nts_jt65,nts_q65,cand,ncand)
|
|
||||||
call timer('get_cand',1)
|
|
||||||
|
|
||||||
do k=1,ncand
|
|
||||||
write(*,1010) k,cand(k)%snr,cand(k)%f,cand(k)%f+77,cand(k)%xdt, &
|
|
||||||
cand(k)%ipol,cand(k)%iflip
|
|
||||||
1010 format(i3,4f10.3,2i3)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
998 call timer('synctest',1)
|
|
||||||
call timer('synctest',101)
|
|
||||||
call fini_timer()
|
|
||||||
|
|
||||||
999 end program synctest
|
|
@ -1,260 +0,0 @@
|
|||||||
module wideband_sync
|
|
||||||
|
|
||||||
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
|
|
||||||
real :: pol !Polarization angle, degrees
|
|
||||||
integer :: ipol !Polarization angle, 1 to 4 ==> 0, 45, 90, 135 deg
|
|
||||||
integer :: iflip !Sync type: JT65 = +/- 1, Q65 = 0
|
|
||||||
integer :: indx
|
|
||||||
end type candidate
|
|
||||||
type sync_dat
|
|
||||||
real :: ccfmax
|
|
||||||
real :: xdt
|
|
||||||
real :: pol
|
|
||||||
integer :: ipol
|
|
||||||
integer :: iflip
|
|
||||||
logical :: birdie
|
|
||||||
end type sync_dat
|
|
||||||
|
|
||||||
parameter (NFFT=32768)
|
|
||||||
parameter (MAX_CANDIDATES=50)
|
|
||||||
parameter (SNR1_THRESHOLD=4.5)
|
|
||||||
type(sync_dat) :: sync(NFFT)
|
|
||||||
integer nkhz_center
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
subroutine get_candidates(ss,savg,jz,nfa,nfb,nts_jt65,nts_q65,cand,ncand)
|
|
||||||
|
|
||||||
! Search symbol spectra ss() over frequency range nfa to nfb (in kHz) for
|
|
||||||
! JT65 and Q65 sync patterns. The nts_* variables are the submode tone
|
|
||||||
! spacings: 1 2 4 8 16 for A B C D E. Birdies are detected and
|
|
||||||
! excised. Candidates are returned in the structure array cand().
|
|
||||||
|
|
||||||
parameter (MAX_PEAKS=100)
|
|
||||||
real ss(322,NFFT),savg(NFFT)
|
|
||||||
real pavg(-20:20)
|
|
||||||
integer indx(NFFT)
|
|
||||||
logical skip
|
|
||||||
type(candidate) :: cand(MAX_CANDIDATES)
|
|
||||||
type(candidate) :: cand0(MAX_CANDIDATES)
|
|
||||||
|
|
||||||
call wb_sync(ss,savg,jz,nfa,nfb,nts_q65) !Output to sync() array
|
|
||||||
|
|
||||||
tstep=2048.0/11025.0 !0.185760 s: 0.5*tsym_jt65, 0.3096*tsym_q65
|
|
||||||
df3=96000.0/NFFT
|
|
||||||
ia=nint(1000*nfa/df3) + 1
|
|
||||||
ib=nint(1000*nfb/df3) + 1
|
|
||||||
if(ia.lt.1) ia=1
|
|
||||||
if(ib.gt.NFFT-1) ib=NFFT-1
|
|
||||||
iz=ib-ia+1
|
|
||||||
|
|
||||||
call indexx(sync(ia:ib)%ccfmax,iz,indx) !Sort by relative snr
|
|
||||||
|
|
||||||
k=0
|
|
||||||
do i=1,MAX_PEAKS
|
|
||||||
n=indx(iz+1-i) + ia - 1
|
|
||||||
f0=0.001*(n-1)*df3
|
|
||||||
snr1=sync(n)%ccfmax
|
|
||||||
if(snr1.lt.SNR1_THRESHOLD) exit
|
|
||||||
flip=sync(n)%iflip
|
|
||||||
if(flip.ne.0.0 .and. nts_jt65.eq.0) cycle
|
|
||||||
if(flip.eq.0.0 .and. nts_q65.eq.0) cycle
|
|
||||||
if(sync(n)%birdie) cycle
|
|
||||||
|
|
||||||
! Test for signal outside of TxT range and set bw for this signal type
|
|
||||||
j1=(sync(n)%xdt + 1.0)/tstep - 1.0
|
|
||||||
j2=(sync(n)%xdt + 52.0)/tstep + 1.0
|
|
||||||
if(flip.ne.0) j2=(sync(n)%xdt + 47.811)/tstep + 1.0
|
|
||||||
ipol=sync(n)%ipol
|
|
||||||
pavg=0.
|
|
||||||
do j=1,j1
|
|
||||||
pavg=pavg + ss(j,n-20:n+20)
|
|
||||||
enddo
|
|
||||||
do j=j2,jz
|
|
||||||
pavg=pavg + ss(j,n-20:n+20)
|
|
||||||
enddo
|
|
||||||
jsum=j1 + (jz-j2+1)
|
|
||||||
pmax=maxval(pavg(-2:2)) !### Why not just pavg(0) ?
|
|
||||||
base=(sum(pavg)-pmax)/jsum
|
|
||||||
pmax=pmax/base
|
|
||||||
if(pmax.gt.5.0) cycle
|
|
||||||
skip=.false.
|
|
||||||
do m=1,k !Skip false syncs within signal bw
|
|
||||||
diffhz=1000.0*(f0-cand(m)%f)
|
|
||||||
bw=nts_q65*110.0
|
|
||||||
if(cand(m)%iflip.ne.0) bw=nts_jt65*178.0
|
|
||||||
if(diffhz.gt.-0.03*bw .and. diffhz.lt.1.03*bw) skip=.true.
|
|
||||||
enddo
|
|
||||||
if(skip) cycle
|
|
||||||
k=k+1
|
|
||||||
cand(k)%snr=snr1
|
|
||||||
cand(k)%f=f0
|
|
||||||
cand(k)%xdt=sync(n)%xdt
|
|
||||||
cand(k)%pol=sync(n)%pol
|
|
||||||
cand(k)%ipol=sync(n)%ipol
|
|
||||||
cand(k)%iflip=nint(flip)
|
|
||||||
cand(k)%indx=n
|
|
||||||
! write(50,3050) i,k,m,f0+32.0,diffhz,bw,snr1,db(snr1)
|
|
||||||
!3050 format(3i5,f8.3,2f8.0,2f8.2)
|
|
||||||
if(k.ge.MAX_CANDIDATES) exit
|
|
||||||
enddo
|
|
||||||
ncand=k
|
|
||||||
|
|
||||||
cand0(1:ncand)=cand(1:ncand)
|
|
||||||
call indexx(cand0(1:ncand)%f,ncand,indx) !Sort by relative snr
|
|
||||||
do i=1,ncand
|
|
||||||
k=indx(i)
|
|
||||||
cand(i)=cand0(k)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
return
|
|
||||||
end subroutine get_candidates
|
|
||||||
|
|
||||||
subroutine wb_sync(ss,savg,jz,nfa,nfb,nts_q65)
|
|
||||||
|
|
||||||
! Compute "orange sync curve" using the Q65 sync pattern
|
|
||||||
|
|
||||||
use timer_module, only: timer
|
|
||||||
parameter (NFFT=32768)
|
|
||||||
parameter (LAGMAX=30)
|
|
||||||
real ss(322,NFFT)
|
|
||||||
real savg(NFFT)
|
|
||||||
real savg_med
|
|
||||||
logical first
|
|
||||||
integer isync(22)
|
|
||||||
integer jsync0(63),jsync1(63)
|
|
||||||
integer ip(1)
|
|
||||||
|
|
||||||
! Q65 sync symbols
|
|
||||||
data isync/1,9,12,13,15,22,23,26,27,33,35,38,46,50,55,60,62,66,69,74,76,85/
|
|
||||||
data jsync0/ &
|
|
||||||
1, 4, 5, 9, 10, 11, 12, 13, 14, 16, 18, 22, 24, 25, 28, 32, &
|
|
||||||
33, 34, 37, 38, 39, 40, 42, 43, 45, 46, 47, 48, 52, 53, 55, 57, &
|
|
||||||
59, 60, 63, 64, 66, 68, 70, 73, 80, 81, 89, 90, 92, 95, 97, 98, &
|
|
||||||
100,102,104,107,108,111,114,119,120,121,122,123,124,125,126/
|
|
||||||
data jsync1/ &
|
|
||||||
2, 3, 6, 7, 8, 15, 17, 19, 20, 21, 23, 26, 27, 29, 30, 31, &
|
|
||||||
35, 36, 41, 44, 49, 50, 51, 54, 56, 58, 61, 62, 65, 67, 69, 71, &
|
|
||||||
72, 74, 75, 76, 77, 78, 79, 82, 83, 84, 85, 86, 87, 88, 91, 93, &
|
|
||||||
94, 96, 99,101,103,105,106,109,110,112,113,115,116,117,118/
|
|
||||||
data first/.true./
|
|
||||||
save first,isync,jsync0,jsync1
|
|
||||||
|
|
||||||
tstep=2048.0/11025.0 !0.185760 s: 0.5*tsym_jt65, 0.3096*tsym_q65
|
|
||||||
if(first) then
|
|
||||||
fac=0.6/tstep
|
|
||||||
do i=1,22 !Expand the Q65 sync stride
|
|
||||||
isync(i)=nint((isync(i)-1)*fac) + 1
|
|
||||||
enddo
|
|
||||||
do i=1,63
|
|
||||||
jsync0(i)=2*(jsync0(i)-1) + 1
|
|
||||||
jsync1(i)=2*(jsync1(i)-1) + 1
|
|
||||||
enddo
|
|
||||||
first=.false.
|
|
||||||
endif
|
|
||||||
|
|
||||||
df3=96000.0/NFFT
|
|
||||||
ia=nint(1000*nfa/df3) + 1 !Flat frequency range for WSE converters
|
|
||||||
ib=nint(1000*nfb/df3) + 1
|
|
||||||
if(ia.lt.1) ia=1
|
|
||||||
if(ib.gt.NFFT-1) ib=NFFT-1
|
|
||||||
|
|
||||||
call pctile(savg(ia:ib),ib-ia+1,50,savg_med)
|
|
||||||
|
|
||||||
lagbest=0
|
|
||||||
ipolbest=1
|
|
||||||
flip=0.
|
|
||||||
|
|
||||||
do i=ia,ib
|
|
||||||
ccfmax=0.
|
|
||||||
do lag=0,LAGMAX
|
|
||||||
|
|
||||||
ccf=0.
|
|
||||||
ccf4=0.
|
|
||||||
do j=1,22 !Test for Q65 sync
|
|
||||||
k=isync(j) + lag
|
|
||||||
ccf4=ccf4 + ss(k,i+1) + ss(k+1,i+1) &
|
|
||||||
+ ss(k+2,i+1)
|
|
||||||
enddo
|
|
||||||
ccf4=ccf4 - savg(i+1)*3*22/float(jz)
|
|
||||||
ccf=ccf4
|
|
||||||
ipol=1
|
|
||||||
if(ccf.gt.ccfmax) then
|
|
||||||
ipolbest=ipol
|
|
||||||
lagbest=lag
|
|
||||||
ccfmax=ccf
|
|
||||||
ccf4best=ccf4
|
|
||||||
flip=0.
|
|
||||||
endif
|
|
||||||
|
|
||||||
ccf=0.
|
|
||||||
ccf4=0.
|
|
||||||
do j=1,63 !Test for JT65 sync, std msg
|
|
||||||
k=jsync0(j) + lag
|
|
||||||
ccf4=ccf4 + ss(k,i+1) + ss(k+1,i+1)
|
|
||||||
enddo
|
|
||||||
ccf4=ccf4 - savg(i+1)*2*63/float(jz)
|
|
||||||
ccf=ccf4
|
|
||||||
ipol=1
|
|
||||||
if(ccf.gt.ccfmax) then
|
|
||||||
ipolbest=ipol
|
|
||||||
lagbest=lag
|
|
||||||
ccfmax=ccf
|
|
||||||
ccf4best=ccf4
|
|
||||||
flip=1.0
|
|
||||||
endif
|
|
||||||
|
|
||||||
ccf=0.
|
|
||||||
ccf4=0.
|
|
||||||
do j=1,63 !Test for JT65 sync, OOO msg
|
|
||||||
k=jsync1(j) + lag
|
|
||||||
ccf4=ccf4 + ss(k,i+1) + ss(k+1,i+1)
|
|
||||||
enddo
|
|
||||||
ccf4=ccf4 - savg(i+1)*2*63/float(jz)
|
|
||||||
ccf=ccf4
|
|
||||||
ipol=1
|
|
||||||
if(ccf.gt.ccfmax) then
|
|
||||||
ipolbest=ipol
|
|
||||||
lagbest=lag
|
|
||||||
ccfmax=ccf
|
|
||||||
ccf4best=ccf4
|
|
||||||
flip=-1.0
|
|
||||||
endif
|
|
||||||
|
|
||||||
enddo ! lag
|
|
||||||
|
|
||||||
poldeg=0.
|
|
||||||
sync(i)%ccfmax=ccfmax
|
|
||||||
sync(i)%xdt=lagbest*tstep-1.0
|
|
||||||
sync(i)%pol=poldeg
|
|
||||||
sync(i)%ipol=ipolbest
|
|
||||||
sync(i)%iflip=flip
|
|
||||||
sync(i)%birdie=.false.
|
|
||||||
if(ccfmax/(savg(i)/savg_med).lt.3.0) sync(i)%birdie=.true.
|
|
||||||
enddo ! i (frequency bin)
|
|
||||||
|
|
||||||
call pctile(sync(ia:ib)%ccfmax,ib-ia+1,50,base)
|
|
||||||
sync(ia:ib)%ccfmax=sync(ia:ib)%ccfmax/base
|
|
||||||
|
|
||||||
bw=65*nts_q65*1.66666667 !Q65-60x bandwidth
|
|
||||||
nbw=bw/df3 + 1 !Number of bins to blank
|
|
||||||
syncmin=2.0
|
|
||||||
nguard=10
|
|
||||||
do i=ia,ib
|
|
||||||
if(sync(i)%ccfmax.lt.syncmin) cycle
|
|
||||||
spk=maxval(sync(i:i+nbw)%ccfmax)
|
|
||||||
ip =maxloc(sync(i:i+nbw)%ccfmax)
|
|
||||||
i0=ip(1)+i-1
|
|
||||||
ja=min(i,i0-nguard)
|
|
||||||
jb=i0+nbw+nguard
|
|
||||||
sync(ja:jb)%ccfmax=0.
|
|
||||||
sync(i0)%ccfmax=spk
|
|
||||||
enddo
|
|
||||||
|
|
||||||
return
|
|
||||||
end subroutine wb_sync
|
|
||||||
|
|
||||||
end module wideband_sync
|
|
@ -352,7 +352,7 @@ void MainWindow::dataSink(int k)
|
|||||||
ndiskdat=0;
|
ndiskdat=0;
|
||||||
datcom_.ndiskdat=0;
|
datcom_.ndiskdat=0;
|
||||||
}
|
}
|
||||||
// Get x and y power, polarized spectrum, nkhz, and ihsym
|
// Get power, spectrum, nkhz, and ihsym
|
||||||
nb=0;
|
nb=0;
|
||||||
if(m_NB) nb=1;
|
if(m_NB) nb=1;
|
||||||
nfsample=96000;
|
nfsample=96000;
|
||||||
@ -427,13 +427,14 @@ void MainWindow::dataSink(int k)
|
|||||||
// qDebug() << "aa" << "Decoder called" << ihsym << ipc_wsjtx[0] << ipc_wsjtx[1]
|
// qDebug() << "aa" << "Decoder called" << ihsym << ipc_wsjtx[0] << ipc_wsjtx[1]
|
||||||
// << ipc_wsjtx[2] << ipc_wsjtx[3] << ipc_wsjtx[4] ;
|
// << ipc_wsjtx[2] << ipc_wsjtx[3] << ipc_wsjtx[4] ;
|
||||||
decode(); //Start the decoder
|
decode(); //Start the decoder
|
||||||
if(m_saveAll and !m_diskData) {
|
if(m_saveAll and !m_diskData and m_nTransmitted<10) {
|
||||||
QString fname=m_saveDir + "/" + t.date().toString("yyMMdd") + "_" +
|
QString fname=m_saveDir + "/" + t.date().toString("yyMMdd") + "_" +
|
||||||
t.time().toString("hhmm");
|
t.time().toString("hhmm");
|
||||||
fname += ".iq";
|
fname += ".iq";
|
||||||
*future2 = QtConcurrent::run(savetf2, fname, false);
|
*future2 = QtConcurrent::run(savetf2, fname, false);
|
||||||
watcher2->setFuture(*future2);
|
watcher2->setFuture(*future2);
|
||||||
}
|
}
|
||||||
|
m_nTransmitted=0;
|
||||||
}
|
}
|
||||||
|
|
||||||
soundInThread.m_dataSinkBusy=false;
|
soundInThread.m_dataSinkBusy=false;
|
||||||
@ -755,6 +756,7 @@ void MainWindow::decoderFinished() //diskWriteFinished
|
|||||||
ui->DecodeButton->setStyleSheet("");
|
ui->DecodeButton->setStyleSheet("");
|
||||||
decodeBusy(false);
|
decodeBusy(false);
|
||||||
decodes_.nQDecoderDone=1;
|
decodes_.nQDecoderDone=1;
|
||||||
|
if(m_diskData) decodes_.nQDecoderDone=2;
|
||||||
mem_q65w.lock();
|
mem_q65w.lock();
|
||||||
memcpy((char*)ipc_wsjtx, &decodes_, sizeof(decodes_));
|
memcpy((char*)ipc_wsjtx, &decodes_, sizeof(decodes_));
|
||||||
mem_q65w.unlock();
|
mem_q65w.unlock();
|
||||||
@ -762,8 +764,6 @@ void MainWindow::decoderFinished() //diskWriteFinished
|
|||||||
t1=t1.asprintf(" %3d/%d ",decodes_.ndecodes,decodes_.ncand);
|
t1=t1.asprintf(" %3d/%d ",decodes_.ndecodes,decodes_.ncand);
|
||||||
lab3->setText(t1);
|
lab3->setText(t1);
|
||||||
QDateTime now=QDateTime::currentDateTimeUtc();
|
QDateTime now=QDateTime::currentDateTimeUtc();
|
||||||
// float secToDecode=0.001*m_decoder_start_time.msecsTo(now);
|
|
||||||
// qDebug() << "bb" << "Decoder Finished" << t1 << secToDecode << now.toString("hh:mm:ss.z");
|
|
||||||
}
|
}
|
||||||
|
|
||||||
void MainWindow::on_actionDelete_all_iq_files_in_SaveDir_triggered()
|
void MainWindow::on_actionDelete_all_iq_files_in_SaveDir_triggered()
|
||||||
@ -984,8 +984,17 @@ void MainWindow::guiUpdate()
|
|||||||
}
|
}
|
||||||
|
|
||||||
if(nsec != m_sec0) { //Once per second
|
if(nsec != m_sec0) { //Once per second
|
||||||
// qDebug() << "AAA" << nsec%60 << ipc_wsjtx[3] << ipc_wsjtx[4]<< m_monitoring;
|
static int n60z=99;
|
||||||
// qDebug() << "BBB" << nsec%60 << decodes_.ndecodes << m_fetched;
|
int n60=nsec%60;
|
||||||
|
int itest[5];
|
||||||
|
mem_q65w.lock();
|
||||||
|
memcpy(&itest, (char*)ipc_wsjtx, 20);
|
||||||
|
mem_q65w.unlock();
|
||||||
|
if(itest[4]==1) m_nTransmitted++;
|
||||||
|
// qDebug() << "AAA" << n60 << itest[0] << itest[1] << itest[2] << itest[3] << itest[4]
|
||||||
|
// << m_nTransmitted;
|
||||||
|
if(n60<n60z) m_nTransmitted=0;
|
||||||
|
n60z=n60;
|
||||||
|
|
||||||
if(m_pctZap>30.0) {
|
if(m_pctZap>30.0) {
|
||||||
lab2->setStyleSheet("QLabel{background-color: #ff0000}");
|
lab2->setStyleSheet("QLabel{background-color: #ff0000}");
|
||||||
|
@ -122,6 +122,7 @@ private:
|
|||||||
qint32 m_dB;
|
qint32 m_dB;
|
||||||
qint32 m_fetched=0;
|
qint32 m_fetched=0;
|
||||||
qint32 m_hsymStop=302;
|
qint32 m_hsymStop=302;
|
||||||
|
qint32 m_nTransmitted=0;
|
||||||
|
|
||||||
double m_fAdd;
|
double m_fAdd;
|
||||||
double m_xavg;
|
double m_xavg;
|
||||||
|
@ -3681,7 +3681,8 @@ void MainWindow::callSandP2(int n)
|
|||||||
QStringList w=m_ready2call[n].split(' ', SkipEmptyParts);
|
QStringList w=m_ready2call[n].split(' ', SkipEmptyParts);
|
||||||
if(m_mode=="Q65") {
|
if(m_mode=="Q65") {
|
||||||
double kHz=w[0].toDouble();
|
double kHz=w[0].toDouble();
|
||||||
m_freqNominal=(1296*1000 + kHz)* 1000;
|
int nMHz=m_freqNominal/1000000;
|
||||||
|
m_freqNominal=(nMHz*1000 + kHz)* 1000;
|
||||||
m_deCall=w[2];
|
m_deCall=w[2];
|
||||||
m_deGrid=w[3];
|
m_deGrid=w[3];
|
||||||
m_txFirst=(w[4]=="0");
|
m_txFirst=(w[4]=="0");
|
||||||
@ -9235,6 +9236,20 @@ void MainWindow::readWidebandDecodes()
|
|||||||
m_EMECall[dxcall].worked=false; //### TEMPORARY ###
|
m_EMECall[dxcall].worked=false; //### TEMPORARY ###
|
||||||
if(w3.contains(grid_regexp)) m_EMECall[dxcall].grid4=w3;
|
if(w3.contains(grid_regexp)) m_EMECall[dxcall].grid4=w3;
|
||||||
m_fetched++;
|
m_fetched++;
|
||||||
|
|
||||||
|
Frequency frequency = (m_freqNominal/1000000) * 1000000 + int(fsked*1000.0);
|
||||||
|
bool bCQ=line.contains(" CQ ");
|
||||||
|
bool bFromDisk=q65wcom.nQDecoderDone==2;
|
||||||
|
if(!bFromDisk and (m_EMECall[dxcall].grid4.contains(grid_regexp) or bCQ)) {
|
||||||
|
qDebug() << "To PSKreporter:" << dxcall << m_EMECall[dxcall].grid4 << frequency << m_mode << nsnr;
|
||||||
|
if (!m_psk_Reporter.addRemoteStation (dxcall, m_EMECall[dxcall].grid4, frequency, m_mode, nsnr)) {
|
||||||
|
showStatusMessage (tr ("Spotting to PSK Reporter unavailable"));
|
||||||
|
}
|
||||||
|
}
|
||||||
|
}
|
||||||
|
|
||||||
|
if (m_config.spot_to_psk_reporter ()) {
|
||||||
|
m_psk_Reporter.sendReport(); // Upload any queued spots
|
||||||
}
|
}
|
||||||
|
|
||||||
// Update "m_wEMECall" by reading q65w_decodes.txt
|
// Update "m_wEMECall" by reading q65w_decodes.txt
|
||||||
|
Loading…
x
Reference in New Issue
Block a user