Correct several VHF/UHF/Microwave items on Rex's list. Specifically:

1. Allow display of JT65 single-line decodes when there is also an
   average decode.
5. Do not call JT4 deep search if Fano decode has succeeded.
7. Fix occasional Fortran error seen with the "#" (nflip=-1) sync.


git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@6678 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
Joe Taylor 2016-05-17 17:19:27 +00:00
parent bd9d772c02
commit f82ee7c4e3
7 changed files with 58 additions and 126 deletions

View File

@ -17,8 +17,8 @@ subroutine decode65b(s2,nflip,nadd,mode65,ntrials,naggressive,ndepth, &
enddo
enddo
call extract(s3,nadd,mode65,ntrials,naggressive,ndepth,mycall,hiscall, &
hisgrid,nexp_decode,ncount,nhist,decoded,ltext,nft,qual)
call extract(s3,nadd,mode65,ntrials,naggressive,ndepth,nflip,mycall, &
hiscall,hisgrid,nexp_decode,ncount,nhist,decoded,ltext,nft,qual)
! Suppress "birdie messages" and other garbage decodes:
if(decoded(1:7).eq.'000AAA ') ncount=-1

View File

@ -56,11 +56,11 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
if(nfsample.eq.12000) call wav11(id2,jz,dd)
if(nfsample.eq.11025) dd(1:jz)=id2(1:jz)
endif
call my_jt4%decode(jt4_decoded,dd,jz,params%nutc,params%nfqso,params%ntol, &
params%emedelay,params%dttol,logical(params%nagain),params%ndepth, &
logical (params%nclearave),params%minsync,params%minw,params%nsubmode, &
params%mycall,params%hiscall,params%hisgrid,params%nlist,params%listutc, &
jt4_average)
call my_jt4%decode(jt4_decoded,dd,jz,params%nutc,params%nfqso, &
params%ntol,params%emedelay,params%dttol,logical(params%nagain), &
params%ndepth,logical(params%nclearave),params%minsync, &
params%minw,params%nsubmode,params%mycall,params%hiscall, &
params%hisgrid,params%nlist,params%listutc,jt4_average)
go to 800
endif
@ -75,12 +75,12 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
newdat65=params%newdat
newdat9=params%newdat
!$call omp_set_dynamic(.true.)
!$omp parallel sections num_threads(2) copyin(/timer_private/) shared(ndecoded) if(.true.) !iif() needed on Mac
!$call omp_set_dynamic(.true.)
!$omp parallel sections num_threads(2) copyin(/timer_private/) shared(ndecoded) if(.true.) !iif() needed on Mac
!$omp section
!$omp section
if(params%nmode.eq.65 .or. (params%nmode.eq.(65+9) .and. params%ntxmode.eq.65)) then
! We're in JT65 mode, or should do JT65 first
! We're in JT65 mode, or should do JT65 first
if(newdat65) dd(1:npts65)=id2(1:npts65)
nf1=params%nfa
nf2=params%nfb
@ -94,7 +94,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
call timer('jt65a ',1)
else if(params%nmode.eq.9 .or. (params%nmode.eq.(65+9) .and. params%ntxmode.eq.9)) then
! We're in JT9 mode, or should do JT9 first
! We're in JT9 mode, or should do JT9 first
call timer('decjt9 ',0)
call my_jt9%decode(jt9_decoded,ss,id2,params%nfqso, &
newdat9,params%npts8,params%nfa,params%nfsplit,params%nfb, &
@ -103,8 +103,8 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
call timer('decjt9 ',1)
endif
!$omp section
if(params%nmode.eq.(65+9)) then !Do the other mode (we're in dual mode)
!$omp section
if(params%nmode.eq.(65+9)) then !Do the other mode (we're in dual mode)
if (params%ntxmode.eq.9) then
if(newdat65) dd(1:npts65)=id2(1:npts65)
nf1=params%nfa
@ -127,9 +127,9 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
end if
endif
!$omp end parallel sections
!$omp end parallel sections
! JT65 is not yet producing info for nsynced, ndecoded.
! JT65 is not yet producing info for nsynced, ndecoded.
ndecoded = my_jt4%decoded + my_jt65%decoded + my_jt9%decoded
800 write(*,1010) nsynced,ndecoded
1010 format('<DecodeFinished>',2i4)
@ -159,18 +159,21 @@ contains
character*2 :: cqual
write(*,3101) 'A',is_deep,is_average,qual,decoded
3101 format(a1,2L3,f6.1,1x,a22)
if (have_sync) then
if (int(qual).gt.0) then
write(cqual, '(i2)') int(qual)
if (ave.gt.0) then
write(*,1000) params%nutc,snr,dt,freq,sync,decoded,cqual, &
write(*,1000) params%nutc,snr,dt,freq,sync,decoded,cqual, &
char(ichar('A')+ich-1), ave
else
write(*,1000) params%nutc,snr,dt,freq,sync,decoded,cqual, &
write(*,1000) params%nutc,snr,dt,freq,sync,decoded,cqual, &
char(ichar('A')+ich-1)
end if
else
write(*,1000) params%nutc,snr,dt,freq,sync,decoded,' *', &
write(*,1000) params%nutc,snr,dt,freq,sync,decoded,' *', &
char(ichar('A')+ich-1)
end if
else
@ -229,12 +232,7 @@ contains
data c/'0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ'/
!$omp critical(decode_results)
! write(*,3301) ft,qual,nsmo,nsum,minsync,naggressive,sync !###
!3301 format('decoded.f90:',6i3,f5.1) !###
decoded=decoded0
! fmt='(i4.4,i4,f5.1,i5,1x,a1,1x,a22,a5)'
! if(single_decode) fmt='(i4.4,i4,f5.1,i5,1x,a2,1x,a22,a5)'
if(ft.eq.0 .and. minsync.ge.0 .and. int(sync).lt.minsync) then
write(*,1010) params%nutc,snr,dt,freq
else
@ -254,7 +252,9 @@ contains
endif
endif
csync='# '
if(single_decode .and. nflip.ne.0 .and. sync.ge.max(0.0,float(minsync))) then
i=0
if(single_decode .and. nflip.ne.0 .and. &
sync.ge.max(0.0,float(minsync))) then
csync='#*'
if(nflip.eq.-1) then
csync='##'
@ -262,6 +262,8 @@ contains
do i=22,1,-1
if(decoded(i:i).ne.' ') exit
enddo
! write(*,*) 'C',i,decoded
if(i.gt.18) i=18
decoded(i+2:i+4)='OOO'
endif
endif
@ -270,7 +272,8 @@ contains
1010 format(i4.4,i4,f5.1,i5,1x,a2,1x,a22,a5)
endif
write(13,1012) params%nutc,nint(sync),snr,dt,float(freq),drift,decoded,ft,nsum,nsmo
write(13,1012) params%nutc,nint(sync),snr,dt,float(freq),drift, &
decoded,ft,nsum,nsmo
1012 format(i4.4,i4,i5,f6.2,f8.0,i4,3x,a22,' JT65',3i3)
call flush(6)

View File

@ -1,5 +1,6 @@
subroutine extract(s3,nadd,mode65,ntrials,naggressive,ndepth,mycall_12, &
hiscall_12,hisgrid,nexp_decode,ncount,nhist,decoded,ltext,nft,qual)
subroutine extract(s3,nadd,mode65,ntrials,naggressive,ndepth,nflip, &
mycall_12,hiscall_12,hisgrid,nexp_decode,ncount,nhist,decoded, &
ltext,nft,qual)
! Input:
! s3 64-point spectra for each of 63 data symbols
@ -91,10 +92,9 @@ subroutine extract(s3,nadd,mode65,ntrials,naggressive,ndepth,mycall_12, &
if(ntotal.le.nd0 .and. rtt.le.r0) nft=1
if(nft.eq.0 .and. iand(ndepth,32).eq.32) then
flip=1.0
qmin=2.0 - 0.1*naggressive
call timer('hint65 ',0)
call hint65(s3,mrs,mrs2,mrsym,mr2sym,mrprob,nadd,flip, &
call hint65(s3,mrs,mrs2,mrsym,mr2sym,mrprob,nadd,nflip, &
mycall,hiscall,hisgrid,nexp_decode,qual,decoded)
if(qual.ge.qmin) then
nft=2

View File

@ -1,4 +1,4 @@
subroutine hint65(s3,mrs,mrs2,mrsym,mr2sym,mrprob,nadd,flip, &
subroutine hint65(s3,mrs,mrs2,mrsym,mr2sym,mrprob,nadd,nflip, &
mycall,hiscall,hisgrid,nexp_decode,qual,decoded)
use packjt
@ -65,7 +65,10 @@ subroutine hint65(s3,mrs,mrs2,mrsym,mr2sym,mrprob,nadd,flip, &
grid2(j)=grid
enddo
10 ncalls=j
if(ncalls.lt.10) stop 'CALL3.TXT very short or missing?'
if(ncalls.lt.10) then
write(*,1010) ncalls
1010 format('CALL3.TXT very short (N =',i2,') or missing?')
endif
close(23)
! NB: generation of test messages is not yet complete!
@ -111,7 +114,6 @@ subroutine hint65(s3,mrs,mrs2,mrsym,mr2sym,mrprob,nadd,flip, &
u1=0.
u1=-99.0
u2=u1
! dtotal=199.0
! Find u1 and u2 (best and second-best) codeword from a list, using
! a bank of matched filters on the symbol spectra s3(i,j).
@ -119,9 +121,9 @@ subroutine hint65(s3,mrs,mrs2,mrsym,mr2sym,mrprob,nadd,flip, &
ipk2=0
msg00=' '
do k=1,nused
if(k.ge.2 .and. k.le.64 .and. flip.lt.0.0) cycle
! Test all messages if flip=+1; skip the CQ messages if flip=-1.
if(flip.gt.0.0 .or. msg0(k)(1:3).ne.'CQ ') then
if(k.ge.2 .and. k.le.64 .and. nflip.lt.0) cycle
! Test all messages if nflip=+1; skip the CQ messages if nflip=-1.
if(nflip.gt.0 .or. msg0(k)(1:3).ne.'CQ ') then
psum=0.
ref=ref0
do j=1,63
@ -145,8 +147,6 @@ subroutine hint65(s3,mrs,mrs2,mrsym,mr2sym,mrprob,nadd,flip, &
ipk2=k
endif
endif
! write(91,3401) k,p,u1,u2,ipk,ipk2,msg0(k)
!3401 format(i6,3f9.3,2i6,2x,a22)
enddo
!### Just in case ???

View File

@ -240,6 +240,7 @@ contains
! If this is a new minute or a new frequency, call avg4
if(.not. prtavg) then
if(nutc.ne.nutc0 .or. abs(nfreq-nfreq0).gt.ntol) then
! This is a new minute or a new frequency, so call avg4.
nutc0=nutc !Try decoding average
nfreq0=nfreq
nsave=nsave+1

View File

@ -8,9 +8,7 @@ module jt65_decode
procedure :: decode
end type jt65_decoder
!
! Callback function to be called with each decode
!
! Callback function to be called with each decode
abstract interface
subroutine jt65_decode_callback(this,sync,snr,dt,freq,drift, &
nflip,width,decoded,ft,qual,nsmo,nsum,minsync)
@ -41,7 +39,7 @@ contains
ntol,nsubmode,minsync,nagain,n2pass,nrobust,ntrials,naggressive, &
ndepth,clearave,mycall,hiscall,hisgrid,nexp_decode)
! Process dd0() data to find and decode JT65 signals.
! Process dd0() data to find and decode JT65 signals.
use jt65_mod
use timer_module, only: timer
@ -98,12 +96,12 @@ contains
robust=nrobust
dd=dd0
ndecoded=0
do ipass=1,n2pass ! 2-pass decoding loop
do ipass=1,n2pass !Two-pass decoding loop
first_time=.true.
if(ipass.eq.1) then !first-pass parameters
if(ipass.eq.1) then !First-pass parameters
thresh0=2.5
nsubtract=1
elseif( ipass.eq.2 ) then !second-pass parameters
elseif( ipass.eq.2 ) then !Second-pass parameters
thresh0=2.5
nsubtract=0
endif
@ -133,12 +131,10 @@ contains
amp=a(2)
f0=(a(3)+ia-1)*df
width=a(4)*df
! write(*,3001) baseline,amp,f0,width
!3001 format('A',4f10.3)
endif
! robust = .false.: use float ccf. Only if ncand>50 fall back to robust (1-bit) ccf
! robust = .true. : use only robust (1-bit) ccf
! robust = .false.: use float ccf. Only if ncand>50 fall back to robust (1-bit) ccf
! robust = .true. : use only robust (1-bit) ccf
ncand=0
if(.not.robust) then
call timer('sync65 ',0)
@ -164,7 +160,6 @@ contains
endif
nvec=ntrials
if(ncand.gt.75) then
! write(*,*) 'Pass ',ipass,' ncandidates too large ',ncand
nvec=100
endif
@ -205,24 +200,18 @@ contains
decoded.eq.' ') nflip=0
if(nft.ne.0) nsum=1
! ncandidates=param(0)
nhard_min=param(1)
! nsoft_min=param(2)
! nera_best=param(3)
nrtt1000=param(4)
ntotal_min=param(5)
! ntry=param(6)
! nq1000=param(7)
! npp1=param(8)
nsmo=param(9)
nfreq=nint(freq+a(1))
ndrift=nint(2.0*a(2))
if(single_decode) then
s2db=sync1 - 30.0 + db(width/3.3) !### VHF/UHF/microwave
s2db=sync1 - 30.0 + db(width/3.3) !### VHF/UHF/microwave
if(nspecial.gt.0) s2db=sync2
else
s2db=10.0*log10(sync2) - 35 !### empirical (HF)
s2db=10.0*log10(sync2) - 35 !### Empirical (HF)
endif
nsnr=nint(s2db)
if(nsnr.lt.-30) nsnr=-30
@ -247,14 +236,13 @@ contains
call this%callback(sync1,nsnr,dtx-1.0,nfreq,ndrift, &
nflip,width,avemsg,nftt,nqave,nsmo,nsum,minsync)
prtavg=.true.
cycle
end if
endif
endif
if(nftt.eq.1) then
nft=1
! nft=1
decoded=avemsg
go to 5
endif
@ -267,11 +255,10 @@ contains
if(rtt.gt.r0(n)) cycle
endif
5 continue
if(decoded.eq.decoded0 .and. abs(freq-freq0).lt. 3.0 .and. &
5 if(decoded.eq.decoded0 .and. abs(freq-freq0).lt. 3.0 .and. &
minsync.ge.0) cycle !Don't display dupes
if(decoded.ne.' ' .or. minsync.lt.0) then
if( nsubtract .eq. 1 ) then
if(nsubtract.eq.1) then
call timer('subtr65 ',0)
call subtract65(dd,npts,freq,dtx)
call timer('subtr65 ',1)
@ -285,7 +272,7 @@ contains
endif
enddo
if(ndupe.ne.1 .or. minsync.lt.0) then
if(ndupe.ne.1 .or. minsync.lt.0) then
if(ipass.eq.1) n65a=n65a + 1
if(ipass.eq.2) n65b=n65b + 1
ndecoded=ndecoded+1
@ -294,9 +281,10 @@ contains
dec(ndecoded)%sync=sync2
dec(ndecoded)%decoded=decoded
nqual=min(qual,9999.0)
if (associated(this%callback)) then
call this%callback(sync1,nsnr,dtx-1.0,nfreq,ndrift, &
nflip,width,decoded,nft,nqual,nsmo,nsum,minsync)
nflip,width,decoded,nft,nqual,nsmo,1,minsync)
end if
endif
decoded0=decoded
@ -447,7 +435,7 @@ contains
enddo
nadd=nsum*ismo
call extract(s3c,nadd,mode65,ntrials,naggressive,ndepth,mycall, &
call extract(s3c,nadd,mode65,ntrials,naggressive,ndepth,nflip,mycall, &
hiscall,hisgrid,nexp_decode,ncount,nhist,avemsg,ltext,nftt,qual)
if(nftt.eq.1) then
nsmo=ismo

View File

@ -1,60 +0,0 @@
subroutine s3avg(nsave,mode65,nutc,nhz,xdt,npol,ntol,s3,nsum,nkv,decoded)
! Save the current synchronized spectra, s3(64,63), for possible
! decoding of average.
real s3(64,63) !Synchronized spectra for 63 symbols
real s3a(64,63,64) !Saved spectra
real s3b(64,63) !Average spectra
integer iutc(64),ihz(64),ipol(64)
real dt(64)
character*22 decoded
logical ltext,first
data first/.true./
save
if(first) then
iutc=-1
ihz=0
ipol=0
first=.false.
ihzdiff=min(100,ntol)
dtdiff=0.2
endif
do i=1,64
if(nutc.eq.iutc(i) .and. abs(nhz-ihz(i)).lt.ihzdiff) then
nsave=mod(nsave-1+64,64)+1
go to 10
endif
enddo
iutc(nsave)=nutc !Save UTC
ihz(nsave)=nhz !Save freq in Hz
ipol(nsave)=npol !Save pol
dt(nsave)=xdt !Save DT
s3a(1:64,1:63,nsave)=s3 !Save the spectra
10 s3b=0.
do i=1,64 !Accumulate avg spectra
if(iutc(i).lt.0) cycle
if(mod(iutc(i),2).ne.mod(nutc,2)) cycle !Use only same sequence
if(abs(nhz-ihz(i)).gt.ihzdiff) cycle !Freq must match
if(abs(xdt-dt(i)).gt.dtdiff) cycle !DT must match
s3b=s3b + s3a(1:64,1:63,i)
nsum=nsum+1
enddo
decoded=' '
if(nsum.ge.2) then !Try decoding the sverage
nadd=mode65*nsum
call extract(s3b,nadd,ncount,nhist,decoded,ltext) !Extract the message
nkv=nsum
if(ncount.lt.0) then
nkv=0
decoded=' '
endif
endif
return
end subroutine s3avg