Merge branch 'release-2.1.0' of bitbucket.org:k1jt/wsjtx into release-2.1.0

This commit is contained in:
Bill Somerville 2019-06-16 22:46:02 +01:00
commit 6a3ad76abb
No known key found for this signature in database
GPG Key ID: D864B06D1E81618F
4 changed files with 219 additions and 204 deletions

View File

@ -8,7 +8,7 @@ subroutine getcandidates4(dd,fa,fb,syncmin,nfqso,maxcand,savg,candidate, &
real x(NFFT1)
real window(NFFT1)
complex cx(0:NH1)
real candidate(3,maxcand)
real candidate(2,maxcand)
real dd(NMAX)
integer ipk(1)
equivalence (x,cx)
@ -64,8 +64,7 @@ subroutine getcandidates4(dd,fa,fb,syncmin,nfqso,maxcand,savg,candidate, &
speak=savsm(i) - 0.25*(savsm(i-1)-savsm(i+1))*del
ncand=ncand+1
candidate(1,ncand)=fpeak
candidate(2,ncand)=-99.99
candidate(3,ncand)=speak
candidate(2,ncand)=speak
if(ncand.eq.maxcand) exit
endif
enddo

View File

@ -9,7 +9,6 @@ subroutine sync4d(cd0,i0,ctwk,itwk,sync)
complex csync2(2*NSS)
complex ctwk(2*NSS)
complex z1,z2,z3,z4
complex zz1,zz2,zz3,zz4
logical first
integer icos4a(0:3),icos4b(0:3),icos4c(0:3),icos4d(0:3)
data icos4a/0,1,3,2/
@ -19,7 +18,7 @@ subroutine sync4d(cd0,i0,ctwk,itwk,sync)
data first/.true./
save first,twopi,csynca,csyncb,csyncc,csyncd,fac
p(z1)=real(z1*fac)**2 + aimag(z1*fac)**2 !Statement function for power
p(z1)=(real(z1*fac)**2 + aimag(z1*fac)**2)**0.5 !Statement function for power
if( first ) then
twopi=8.0*atan(1.0)
@ -60,11 +59,12 @@ subroutine sync4d(cd0,i0,ctwk,itwk,sync)
z4=0.
if(itwk.eq.1) csync2=ctwk*csynca !Tweak the frequency
z1=0.
if(i1.ge.0 .and. i1+4*NSS-1.le.NP-1) then
z1=sum(cd0(i1:i1+4*NSS-1:2)*conjg(csync2))
elseif( i1.lt.0 ) then
npts=(i1+4*NSS-1)/2
if(npts.le.8) then
if(npts.le.16) then
z1=0.
else
z1=sum(cd0(0:i1+4*NSS-1:2)*conjg(csync2(2*NSS-npts:)))
@ -78,16 +78,18 @@ subroutine sync4d(cd0,i0,ctwk,itwk,sync)
if(i3.ge.0 .and. i3+4*NSS-1.le.NP-1) z3=sum(cd0(i3:i3+4*NSS-1:2)*conjg(csync2))
if(itwk.eq.1) csync2=ctwk*csyncd !Tweak the frequency
z4=0.
if(i4.ge.0 .and. i4+4*NSS-1.le.NP-1) then
z4=sum(cd0(i4:i4+4*NSS-1:2)*conjg(csync2))
elseif( i4+4*NSS-1.gt.NP-1 ) then
npts=(NP-1-i4+1)/2
if(npts.le.8) then
if(npts.le.16) then
z4=0.
else
z4=sum(cd0(i4:i4+2*npts-1:2)*conjg(csync2(1:npts)))
endif
endif
sync = p(z1) + p(z2) + p(z3) + p(z4)
return

View File

@ -50,7 +50,7 @@ contains
real bitmetrics(2*NN,3)
real dd(NMAX)
real llr(2*ND),llra(2*ND),llrb(2*ND),llrc(2*ND),llrd(2*ND)
real candidate(3,100)
real candidate(2,100)
real savg(NH1),sbase(NH1)
integer apbits(2*ND)
@ -229,7 +229,7 @@ contains
dobigfft=.true.
do icand=1,ncand
f0=candidate(1,icand)
snr=candidate(3,icand)-1.0
snr=candidate(2,icand)-1.0
call timer('ft4_down',0)
call ft4_downsample(dd,dobigfft,f0,cd2) !Downsample to 32 Sam/Sym
call timer('ft4_down',1)
@ -237,6 +237,7 @@ contains
sum2=sum(cd2*conjg(cd2))/(real(NMAX)/real(NDOWN))
if(sum2.gt.0.0) cd2=cd2/sqrt(sum2)
! Sample rate is now 12000/18 = 666.67 samples/second
do iseg=1,3 ! DT search is done over 3 segments
do isync=1,2
if(isync.eq.1) then
idfmin=-12
@ -244,6 +245,17 @@ contains
idfstp=3
ibmin=-344
ibmax=1012
if(iseg.eq.1) then
ibmin=108
ibmax=560
elseif(iseg.eq.2) then
smax1=smax
ibmin=560
ibmax=1012
elseif(iseg.eq.3) then
ibmin=-344
ibmax=108
endif
ibstp=4
else
idfmin=idfbest-4
@ -254,8 +266,8 @@ contains
ibstp=1
endif
ibest=-1
smax=-99.
idfbest=0
smax=-99.
call timer('sync4d ',0)
do idf=idfmin,idfmax,idfstp
do istart=ibmin,ibmax,ibstp
@ -269,11 +281,13 @@ contains
enddo
call timer('sync4d ',1)
enddo
if(iseg.eq.1) smax1=smax
if(smax.lt.0.7) cycle
f0=f0+real(idfbest)
if( f0.le.10.0 .or. f0.ge.4990.0 ) cycle
if(iseg.gt.1 .and. smax.lt.smax1) cycle
f1=f0+real(idfbest)
if( f1.le.10.0 .or. f1.ge.4990.0 ) cycle
call timer('ft4down ',0)
call ft4_downsample(dd,dobigfft,f0,cb) !Final downsample, corrected f0
call ft4_downsample(dd,dobigfft,f1,cb) !Final downsample, corrected f0
call timer('ft4down ',1)
sum2=sum(abs(cb)**2)/(real(NSS)*NN)
if(sum2.gt.0.0) cb=cb/sqrt(sum2)
@ -285,12 +299,10 @@ contains
else
cd(-ibest:ibest+NN*NSS-1)=cb(0:NN*NSS+2*ibest-1)
endif
call timer('bitmet ',0)
call get_ft4_bitmetrics(cd,bitmetrics,badsync)
call timer('bitmet ',1)
if(badsync) cycle
hbits=0
where(bitmetrics(:,1).ge.0) hbits=1
ns1=count(hbits( 1: 8).eq.(/0,0,0,1,1,0,1,1/))
@ -343,7 +355,7 @@ contains
!
! Conditions that cause us to bail out of AP decoding
napwid=50
if(ncontest.le.4 .and. iaptype.ge.3 .and. (abs(f0-nfqso).gt.napwid) ) cycle
if(ncontest.le.4 .and. iaptype.ge.3 .and. (abs(f1-nfqso).gt.napwid) ) cycle
if(iaptype.ge.2 .and. apbits(1).gt.1) cycle ! No, or nonstandard, mycall
if(iaptype.ge.3 .and. apbits(30).gt.1) cycle ! No, or nonstandard, dxcall
@ -405,9 +417,9 @@ contains
if(doosd .and. nharderror.lt.0) then
ndeep=3
if(abs(nfqso-f1).le.napwid) then
ndeep=4
endif
! if(abs(nfqso-f1).le.napwid) then
! ndeep=4
! endif
call timer('osd174_91 ',0)
call osd174_91(llr,apmask,ndeep,message77,cw,nharderror,dmin)
call timer('osd174_91 ',1)
@ -422,7 +434,7 @@ contains
call get_ft4_tones_from_77bits(message77,i4tone)
dt=real(ibest)/666.67
call timer('subtract',0)
call subtractft4(dd,i4tone,f0,dt)
call subtractft4(dd,i4tone,f1,dt)
call timer('subtract',1)
endif
idupe=0
@ -439,11 +451,14 @@ contains
endif
nsnr=nint(max(-21.0,xsnr))
xdt=ibest/666.67 - 0.5
!write(21,'(i6.6,i5,2x,f4.1,i6,2x,a37,2x,f4.1,3i3,f5.1)') nutc,nsnr,xdt,nint(f0),message,sync,iaptype,ipass,isp,dmin
call this%callback(sync,nsnr,xdt,f0,message,iaptype,qual)
!write(21,'(i6.6,i5,2x,f4.1,i6,2x,a37,2x,f4.1,3i3,f5.1,i4,i4,i4)') &
! nutc,nsnr,xdt,nint(f1),message,smax,iaptype,ipass,isp,dmin,nsync_qual,nharderror,iseg
call this%callback(smax,nsnr,xdt,f1,message,iaptype,qual)
exit
endif
enddo !Sequence estimation
if(nharderror.ge.0) exit
enddo !3 DT segments
enddo !Candidate list
enddo !Subtraction loop
return

View File

@ -179,7 +179,6 @@ program jt9
go to 999
endif
if(mode.eq.5) ndepth=3
allocate(shared_data)
nflatten=0