Fix a conflict between noise baseline percentile level and noise blanker percentage. Both were using the npct variable. Add an option for an FST4 pass when in FST4W mode.

This commit is contained in:
Steven Franke 2021-01-02 10:09:44 -06:00
parent a3638c456a
commit ebb6e5b697

View File

@ -43,6 +43,7 @@ contains
procedure(fst4_decode_callback) :: callback
character*37 decodes(100)
character*37 msg,msgsent
character*8 s_nfa_nfb
character*20 wcalls(MAXWCALLS), wpart
character*77 c77
character*12 mycall,hiscall
@ -58,7 +59,6 @@ contains
logical lagain,lapcqonly
integer itone(NN)
integer hmod
integer ipct(0:7)
integer*1 apmask(240),cw(240),hdec(240)
integer*1 message101(101),message74(74),message77(77)
integer*1 rvec(77)
@ -74,7 +74,6 @@ contains
integer*2 iwave(30*60*12000)
data ipct/0,8,14,4,12,2,10,6/
data mcq/0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,0,0/
data mrrr/0,1,1,1,1,1,1,0,1,0,0,1,0,0,1,0,0,0,1/
data m73/0,1,1,1,1,1,1,0,1,0,0,1,0,1,0,0,0,0,1/
@ -247,6 +246,7 @@ contains
do_k50_decode=.false.
endif
! Noise blanker setup
ndropmax=1
single_decode=iand(nexp_decode,32).ne.0
npct=0
@ -262,16 +262,41 @@ contains
inb2=1 !Try NB = 0, 1, 2,... 20%
else
inb1=0 !Fixed NB value, 0 to 25%
ipct(0)=npct
endif
! If environment variable FST4W_ALSO_FST4 exists then, when in FST4W mode,
! do a second pass for FST4 decodes. The value of FST4W_ALSO_FST4
! is of the form xxxxyyyy where nfa=xxxx and nfb=yyyy are the
! search limits for the FST4 decoding pass, e.g.
! FST4W_ALSO_FST4=08001700 will set FST4 search window to [800Hz,1700Hz]
!
nmode=1
call get_environment_variable("FST4W_ALSO_FST4",s_nfa_nfb,nlength)
if(iwspr.eq.1 .and. nlength.eq.8) then
read(s_nfa_nfb,"(i4.4,i4.4)") nfa_mode2,nfb_mode2
nmode=2
endif
do imode=1,nmode
if(imode.eq.1) iwspr=1
if(imode.eq.2) then ! this is FST4 after a FST4W pass
iwspr=0
nfa=nfa_mode2
nfb=nfb_mode2
endif
! nfa,nfb: define the noise-baseline analysis window
! fa, fb: define the signal search window
! We usually make nfa<fa and nfb>fb so that noise baseline analysis
! window extends outside of the [fa,fb] window where we think the signals are.
!
if(iwspr.eq.1) then !FST4W
!300 Hz wide noise-fit window
nfa=max(100,nint(nfqso+1.5*baud-150))
nfb=min(4800,nint(nfqso+1.5*baud+150))
nfa=max(100,nfqso-ntol-100)
nfb=min(4800,nfqso+ntol+100)
fa=max(100,nint(nfqso+1.5*baud-ntol)) ! signal search window
fb=min(4800,nint(nfqso+1.5*baud+ntol))
else if(single_decode) then
else if(iwspr.eq.0) then
if(imode.eq.1 .and. single_decode) then
fa=max(100,nint(nfa+1.5*baud))
fb=min(4800,nint(nfb+1.5*baud))
! extend noise fit 100 Hz outside of search window
@ -284,12 +309,13 @@ contains
nfa=max(100,nfa-100)
nfb=min(4800,nfb+100)
endif
endif
ndecodes=0
decodes=' '
new_callsign=.false.
do inb=0,inb1,inb2
if(nb.lt.0) npct=inb
if(nb.lt.0) npct=inb ! we are looping over blanker settings
call blanker(iwave,nfft1,ndropmax,npct,c_bigfft)
! The big fft is done once and is used for calculating the smoothed spectrum
@ -308,14 +334,13 @@ contains
do icand=1,ncand
fc0=candidates0(icand,1)
if(iwspr.eq.0 .and. nb.lt.0 .and. npct.ne.0 .and. &
abs(fc0-(nfqso+1.5*baud)).gt.ntol) cycle
abs(fc0-(nfqso+1.5*baud)).gt.ntol) cycle ! blanker loop only near nfqso
detmet=candidates0(icand,2)
! Downconvert and downsample a slice of the spectrum centered on the
! rough estimate of the candidates frequency.
! Output array c2 is complex baseband sampled at 12000/ndown Sa/sec.
! The size of the downsampled c2 array is nfft2=nfft1/ndown
call timer('dwnsmpl ',0)
call fst4_downsample(c_bigfft,nfft1,ndown,fc0,sigbw,c2)
call timer('dwnsmpl ',1)
@ -355,8 +380,8 @@ contains
enddo
ncand=ic
! If FST4 and Single Decode is not checked, then find candidates within
! 20 Hz of nfqso and put them at the top of the list
! If FST4 mode and Single Decode is not checked, then find candidates
! within 20 Hz of nfqso and put them at the top of the list
if(iwspr.eq.0 .and. .not.single_decode) then
nclose=count(abs(candidates0(:,3)-(nfqso+1.5*baud)).le.20)
k=0
@ -602,14 +627,14 @@ contains
hd=sum(ieor(hdec,cw)*abs(llrs(:,1))) ! weighted distance wrt N=1 symbols
open(21,file=trim(data_dir)//'/fst4_decodes.dat',status='unknown',position='append')
write(21,3021) nutc,icand,itry,nsyncoh,iaptype, &
ijitter,ntype,Keff,nsync_qual,nharderrors,dmin,nhp,hd, &
ijitter,npct,ntype,Keff,nsync_qual,nharderrors,dmin,nhp,hd, &
sync,xsnr,xdt,fsig,w50,trim(msg)
3021 format(i6.6,i4,5i3,3i4,f6.1,i4,f6.1,f9.2,f6.1,f6.2,f7.1,f7.3,1x,a)
3021 format(i6.6,i4,6i3,3i4,f6.1,i4,f6.1,f9.2,f6.1,f6.2,f7.1,f7.3,1x,a)
close(21)
endif
call this%callback(nutc,smax1,nsnr,xdt,fsig,msg, &
iaptype,qual,ntrperiod,lwspr,fmid,w50)
if(iwspr.eq.0 .and. nb.lt.0) go to 900
if(iwspr.eq.0 .and. nb.lt.0 .and. imode.eq.1) go to 900
goto 800
endif
enddo ! metrics
@ -625,6 +650,8 @@ contains
close(42)
endif
enddo ! mode loop
900 return
end subroutine decode
@ -818,8 +845,8 @@ contains
do i=ina,inb !Compute CCF of s() and 4 tones
s2(i)=s(i-hmod*3) + s(i-hmod) +s(i+hmod) +s(i+hmod*3)
enddo
npct=30
call fst4_baseline(s2,nnw,ina+hmod*3,inb-hmod*3,npct,sbase)
npctile=30
call fst4_baseline(s2,nnw,ina+hmod*3,inb-hmod*3,npctile,sbase)
if(any(sbase(ina:inb).le.0.0)) return
s2(ina:inb)=s2(ina:inb)/sbase(ina:inb) !Normalize wrt noise level