Merge branch 'feat-early_decode' into release-2.5.0

This commit is contained in:
Joe Taylor 2021-07-09 12:13:15 -04:00
commit 1d3025329b
8 changed files with 86 additions and 42 deletions

View File

@ -8,7 +8,7 @@ extern qint16 id[4*60*96000];
void getfile(QString fname, bool xpol, int dbDgrd)
{
int npts=2*52*96000;
int npts=2*56*96000;
if(xpol) npts=2*npts;
// Degrade S/N by dbDgrd dB -- for tests only!!

View File

@ -6,15 +6,18 @@ subroutine decode0(dd,ss,savg,nstandalone)
real*4 dd(4,NSMAX),ss(4,322,NFFT),savg(4,NFFT)
real*8 fcenter
integer hist(0:32768)
logical ldecoded
character mycall*12,hiscall*12,mygrid*6,hisgrid*6,datetime*20
character mycall0*12,hiscall0*12,hisgrid0*6
common/npar/fcenter,nutc,idphi,mousedf,mousefqso,nagain, &
ndepth,ndiskdat,neme,newdat,nfa,nfb,nfcal,nfshift, &
mcall3,nkeep,ntol,nxant,nrxlog,nfsample,nxpol,nmode, &
nfast,nsave,max_drift,nhsym,mycall,mygrid,hiscall,hisgrid,datetime
common/early/nhsym1,nhsym2,ldecoded(32768)
data neme0/-99/,mcall3b/1/
save
call sec0(0,tquick)
call timer('decode0 ',0)
if(newdat.ne.0) then
nz=96000*nhsym/5.3833
@ -51,12 +54,16 @@ subroutine decode0(dd,ss,savg,nstandalone)
call map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
mousedf,mousefqso,nagain,ndecdone,nfshift,ndphi,max_drift, &
nfcal,nkeep,mcall3b,nsum,nsave,nxant,mycall,mygrid, &
neme,ndepth,nstandalone,hiscall,hisgrid,nhsym,nfsample,nxpol,nmode)
neme,ndepth,nstandalone,hiscall,hisgrid,nhsym,nfsample, &
ndiskdat,nxpol,nmode)
call timer('map65a ',1)
call timer('decode0 ',1)
write(*,1010) nsum,nsave
1010 format('<DecodeFinished>',2i4)
call sec0(1,tdec)
if(nhsym.eq.nhsym1) write(*,1010) nsum,nsave,nstandalone,nhsym,tdec
1010 format('<EarlyFinished>',3i4,i6,f6.2)
if(nhsym.eq.nhsym2) write(*,1012) nsum,nsave,nstandalone,nhsym,tdec
1012 format('<DecodeFinished>',3i4,i6,f6.2)
flush(6)
return

View File

@ -32,7 +32,7 @@ program m65
integer*2 i2(NREAD)
real*8 hsym
real*4 ssz5a(NFFT)
logical*1 lstrong(0:1023)
logical*1 lstrong(0:1023),ldecoded,eof
real*8 fc0,fcenter
character*80 arg,infile
character mycall*12,hiscall*12,mygrid*6,hisgrid*6,datetime*20
@ -41,6 +41,7 @@ program m65
ndepth,ndiskdat,neme,newdat,nfa,nfb,nfcal,nfshift, &
mcall3,nkeep,ntol,nxant,nrxlog,nfsample,nxpol,nmode, &
nfast,nsave,max_drift,nhsym,mycall,mygrid,hiscall,hisgrid,datetime
common/early/nhsym1,nhsym2,ldecoded(32768)
nargs=iargc()
if(nargs.ne.1 .and. nargs.lt.5) then
@ -52,6 +53,9 @@ program m65
print*,' (Gets data from MAP65, via shared memory region.)'
go to 999
endif
nstandalone=1
nhsym1=280
nhsym2=302
call getarg(1,arg)
if(arg(1:2).eq.'-s') then
call m65a
@ -124,9 +128,12 @@ program m65
nch=2
if(nxpol.eq.1) nch=4
eof=.false.
do irec=1,9999999
read(10,end=10) i2
if(.not.eof) read(10,end=4) i2
go to 6
4 eof=.true.
6 if(eof) i2=0
do i=1,NREAD,nch
k=k+1
if(k.gt.60*96000) exit
@ -156,15 +163,18 @@ program m65
rejecty,pxdb,pydb,ssz5a,nkhz,ihsym,nzap,slimit,lstrong)
call timer('symspec ',1)
nhsym0=nhsym
nutc=nutc0
if(nhsym.eq.nhsym1) call decode0(dd,ss,savg,nstandalone)
if(nhsym.eq.nhsym2) then
call decode0(dd,ss,savg,nstandalone)
exit
endif
endif
enddo ! irec
10 continue
if(iqadjust.ne.0) write(*,3002) rejectx,rejecty
3002 format('Image rejection:',2f7.1,' dB')
nutc=nutc0
nstandalone=1
call decode0(dd,ss,savg,nstandalone)
enddo ! ifile
call timer('m65 ',1)

View File

@ -73,6 +73,7 @@ subroutine m65c(dd,ss,savg,nparams0)
real*4 dd(4,5760000),ss(4,322,32768),savg(4,32768)
real*8 fcenter
integer nparams0(41),nparams(41)
logical ldecoded
character*12 mycall,hiscall
character*6 mygrid,hisgrid
character*20 datetime
@ -80,6 +81,7 @@ subroutine m65c(dd,ss,savg,nparams0)
ndepth,ndiskdat,neme,newdat,nfa,nfb,nfcal,nfshift, &
mcall3,nkeep,ntol,nxant,nrxlog,nfsample,nxpol,nmode, &
nfast,nsave,max_drift,nhsym,mycall,mygrid,hiscall,hisgrid,datetime
common/early/nhsym1,nhsym2,ldecoded(32768)
equivalence (nparams,fcenter)
nparams=nparams0 !Copy parameters into common/npar/

View File

@ -1,7 +1,8 @@
subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
mousedf,mousefqso,nagain,ndecdone,nfshift,ndphi,max_drift, &
nfcal,nkeep,mcall3b,nsum,nsave,nxant,mycall,mygrid, &
neme,ndepth,nstandalone,hiscall,hisgrid,nhsym,nfsample,nxpol,nmode)
neme,ndepth,nstandalone,hiscall,hisgrid,nhsym,nfsample, &
ndiskdat,nxpol,nmode)
! Processes timf2 data from Linrad to find and decode JT65 signals.
@ -24,6 +25,7 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
logical done(MAXMSG)
logical xpol,bq65,q65b_called
logical candec(MAX_CANDIDATES)
logical ldecoded
character decoded*22,blank*22,cmode*2
real short(3,NFFT) !SNR dt ipol for potential shorthands
real qphi(12)
@ -31,24 +33,29 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
common/c3com/ mcall3a
common/testcom/ifreq
common/early/nhsym1,nhsym2,ldecoded(32768)
data blank/' '/,cm/'#'/
data shmsg0/'ATT','RO ','RRR','73 '/
data nfile/0/,nutc0/-999/,nid/0/,ip000/1/,ip001/1/,mousefqso0/-999/
save
call sec0(0,tquick)
ldecoded=.false.
if(nhsym.eq.nhsym1 .or. newdat.ne.0 .or. nagain.ne.0) ldecoded=.false.
nkhz_center=nint(1000.0*(fcenter-int(fcenter)))
mfa=nfa-nkhz_center+48
mfb=nfb-nkhz_center+48
mode65=mod(nmode,10)
if(mode65.eq.3) mode65=4
mode_q65=nmode/10
xpol=(nxpol.ne.0)
nts_jt65=2**(mode65-1) !JT65 tone separation factor
nts_q65=2**(mode_q65-1) !Q65 tone separation factor
xpol=(nxpol.ne.0)
if(nhsym.eq.nhsym1) ldecoded=.false. !Clean start for Q65 at early decode
! No second decode for JT65?
if(nhsym.eq.nhsym2 .and. (nstandalone.eq.1 .or. ndiskdat.eq.0)) mode65=0
if(nagain.eq.0) then
call timer('get_cand',0)
call get_candidates(ss,savg,xpol,nhsym,mfa,mfb,nts_jt65,nts_q65,cand,ncand)
@ -59,8 +66,8 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
! do k=1,ncand
! freq=cand(k)%f+nkhz_center-48.0-1.27046
! write(*,3010) nutc,k,db(cand(k)%snr),cand(k)%f,freq,cand(k)%xdt, &
! cand(k)%ipol,cand(k)%iflip
!3010 format('=a',i5.4,i5,f8.2,3f10.3,2i3)
! cand(k)%ipol,cand(k)%iflip,cand(k)%indx
!3010 format('=a',i5.4,i5,f8.2,3f10.3,2i3,i6)
! enddo
!###
@ -112,7 +119,9 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
short=0. !Zero the whole short array
jpz=1
if(xpol) jpz=4
if(mode65.eq.0) go to 50
! First steps for JT65 decoding
do i=ia,ib !Search over freq range
freq=0.001*(i-16385)*df
! Find the local base level for each polarization; update every 10 bins.
@ -279,8 +288,9 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
endif
enddo !i=ia,ib
if(nqd.eq.1) then
50 if(nqd.eq.1) then
nwrite=0
if(mode65.eq.0) km=0
do k=1,km
decoded=msg(k)
if(decoded.ne.' ') then
@ -351,7 +361,7 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
call timer('q65b ',0)
call q65b(nutc,nqd,nxant,fcenter,nfcal,nfsample,ikhz,mousedf, &
ntol,xpol,mycall,mygrid, hiscall,hisgrid,mode_q65,f0,fqso, &
newdat,nagain,max_drift,idec)
newdat,nagain,max_drift,nhsym,idec)
call timer('q65b ',1)
if(idec.ge.0) candec(icand)=.true.
enddo
@ -362,7 +372,7 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
call timer('q65b ',0)
call q65b(nutc,nqd,nxant,fcenter,nfcal,nfsample,ikhz,mousedf, &
ntol,xpol,mycall,mygrid,hiscall,hisgrid,mode_q65,f0,fqso, &
newdat,nagain,max_drift,idec)
newdat,nagain,max_drift,nhsym,idec)
call timer('q65b ',1)
endif
endif
@ -380,15 +390,17 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
if(ndphi.eq.1 .and.iloop.eq.12) call getdphi(qphi)
if(nqd.eq.1) then
write(*,1013) nsum,nsave
1013 format('<QuickDecodeDone>',2i4)
call sec0(1,tdec)
write(*,1013) nsum,nsave,nstandalone,nhsym,tdec
1013 format('<QuickDecodeDone>',3i4,i6,f6.2)
flush(6)
call sec0(1,tquick)
open(16,file='tquick.dat',status='unknown',access='append')
write(16,1016) nutc,tquick
write(16,1016) nutc,tdec
1016 format(i4.4,f7.1)
close(16)
endif
call sec0(1,tsec0)
if(nhsym.eq.nhsym1 .and. tsec0.gt.3.0) go to 900
if(nqd.eq.1 .and. nagain.eq.1) go to 900
if(nqd.eq.0 .and. bq65) then
@ -404,11 +416,12 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
call timer('q65b ',0)
call q65b(nutc,nqd,nxant,fcenter,nfcal,nfsample,ikhz,mousedf,ntol, &
xpol,mycall,mygrid,hiscall,hisgrid,mode_q65,f0,fqso,newdat, &
nagain,max_drift,idec)
nagain,max_drift,nhsym,idec)
call timer('q65b ',1)
if(idec.ge.0) candec(icand)=.true.
enddo ! icand
endif
call sec0(1,tsec0)
enddo ! nqd
@ -491,11 +504,8 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb, &
write(21,1100) f0,ndf,dt,npol,nsync2,nutc,decoded,cp, &
cmode(1:1),cmode(2:2)
1100 format(f8.3,i5,f5.1,2i4,i5.4,2x,a22,2x,a1,3x,a1,1x,a1)
! write(21,1014) f0,ndf,ndf0,ndf1,ndf2,dt,npol,nsync1, &
! nutc,decoded,cp,cmode
endif
endif
j=j+nsiz(n)
enddo !i=1,km

View File

@ -1,6 +1,6 @@
subroutine q65b(nutc,nqd,nxant,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,xpol, &
mycall0,mygrid,hiscall0,hisgrid,mode_q65,f0,fqso,newdat,nagain, &
max_drift,idec)
max_drift,nhsym,idec)
! This routine provides an interface between MAP65 and the Q65 decoder
! in WSJT-X. All arguments are input data obtained from the MAP65 GUI.
@ -22,7 +22,7 @@ subroutine q65b(nutc,nqd,nxant,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,xpol, &
integer*2 iwave(60*12000)
complex ca(MAXFFT1),cb(MAXFFT1) !FFTs of raw x,y data
complex cx(0:MAXFFT2-1),cy(0:MAXFFT2-1),cz(0:MAXFFT2)
logical xpol
logical xpol,ldecoded
integer ipk1(1)
real*8 fcenter,freq0,freq1
character*12 mycall0,hiscall0
@ -33,6 +33,7 @@ subroutine q65b(nutc,nqd,nxant,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,xpol, &
character*80 wsjtx_dir
character*1 cp,cmode*2
common/cacb/ca,cb
common/early/nhsym1,nhsym2,ldecoded(32768)
save
open(9,file='wsjtx_dir.txt',status='old')

View File

@ -7,6 +7,7 @@ module wideband_sync
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
@ -21,7 +22,6 @@ module wideband_sync
parameter (MAX_CANDIDATES=50)
parameter (SNR1_THRESHOLD=4.5)
type(sync_dat) :: sync(NFFT)
logical ldecoded(NFFT)
integer nkhz_center
contains
@ -37,8 +37,9 @@ subroutine get_candidates(ss,savg,xpol,jz,nfa,nfb,nts_jt65,nts_q65,cand,ncand)
real ss(4,322,NFFT),savg(4,NFFT)
real pavg(-20:20)
integer indx(NFFT)
logical xpol,skip
logical xpol,skip,ldecoded
type(candidate) :: cand(MAX_CANDIDATES)
common/early/nhsym1,nhsym2,ldecoded(32768)
call wb_sync(ss,savg,xpol,jz,nfa,nfb)
@ -95,6 +96,7 @@ subroutine get_candidates(ss,savg,xpol,jz,nfa,nfb,nts_jt65,nts_q65,cand,ncand)
cand(k)%pol=sync(n)%pol
cand(k)%ipol=sync(n)%ipol
cand(k)%iflip=nint(flip)
cand(k)%indx=n
if(k.ge.MAX_CANDIDATES) exit
enddo
ncand=k

View File

@ -620,8 +620,16 @@ void MainWindow::dataSink(int k)
n=0;
}
// if(ihsym == 280) { //For JT65, decode at t=52 s (also for old *.tf2/*.iq disk files)
if(ihsym == 302) { //For Q65, decode at t=56 s
if(ihsym == 280 and !m_diskData) { //Early decode, t=52 s
datcom_.newdat=1;
datcom_.nagain=0;
datcom_.nhsym=ihsym;
QDateTime t = QDateTime::currentDateTimeUtc();
m_dateTime=t.toString("yyyy-MMM-dd hh:mm");
decode(); //Start the decoder
}
if(ihsym == 302) { //Decode at t=56 s (for Q65 and data from disk)
datcom_.newdat=1;
datcom_.nagain=0;
datcom_.nhsym=ihsym;
@ -637,6 +645,7 @@ void MainWindow::dataSink(int k)
watcher2->setFuture(*future2);
}
}
soundInThread.m_dataSinkBusy=false;
}
@ -1372,7 +1381,8 @@ void MainWindow::readFromStdout() //readFromStdout
lab7->setText (QString {"Avg: %1"}.arg (m_nsum));
if(m_modeQ65>0) m_wide_graph_window->setDecodeFinished();
}
if(t.indexOf("<DecodeFinished>") >= 0) {
if((t.indexOf("<EarlyFinished>") >= 0) or (t.indexOf("<DecodeFinished>") >= 0)) {
if(m_widebandDecode) {
m_messages_window->setText(m_messagesText,m_bandmapText);
m_band_map_window->setText(m_bandmapText);
@ -1380,10 +1390,12 @@ void MainWindow::readFromStdout() //readFromStdout
}
QFile lockFile(m_appDir + "/.lock");
lockFile.open(QIODevice::ReadWrite);
ui->DecodeButton->setStyleSheet("");
decodeBusy(false);
m_map65RxLog=0;
m_startAnother=m_loopall;
if(t.indexOf("<DecodeFinished>") >= 0) {
ui->DecodeButton->setStyleSheet("");
decodeBusy(false);
m_map65RxLog=0;
m_startAnother=m_loopall;
}
return;
}