Radionalize the reporting of idec values.

This commit is contained in:
Joe Taylor 2021-01-14 13:13:40 -05:00
parent 0abdff0216
commit fca6d482f7
4 changed files with 73 additions and 58 deletions

View File

@ -776,18 +776,13 @@ contains
character*3 cflags character*3 cflags
cflags=' ' cflags=' '
if(idec.gt.0) then if(idec.ge.0) then
iaptype=idec iaptype=idec
navg=0 navg=0
if(idec.ge.100) then if(idec.ge.100) then
iaptype=idec/100 iaptype=idec/100
navg=mod(idec,100) navg=mod(idec,100)
endif endif
if(iaptype.eq.1) then
iaptype=3
else
iaptype=iaptype-2
endif
cflags='q ' cflags='q '
write(cflags(2:2),'(i1)') iaptype write(cflags(2:2),'(i1)') iaptype
if(navg.ge.2) write(cflags(3:3),'(i1)') navg if(navg.ge.2) write(cflags(3:3),'(i1)') navg

View File

@ -29,7 +29,7 @@ contains
ntol,ndepth,lclearave,emedelay,mycall,hiscall,hisgrid,nQSOprogress, & ntol,ndepth,lclearave,emedelay,mycall,hiscall,hisgrid,nQSOprogress, &
ncontest,lapcqonly) ncontest,lapcqonly)
! Decodes Q65 signals ! Top-level routine that organizes the decoding of Q65 signals
! Input: iwave Raw data, i*2 ! Input: iwave Raw data, i*2
! nutc UTC for time-tagging the decode ! nutc UTC for time-tagging the decode
! ntrperiod T/R sequence length (s) ! ntrperiod T/R sequence length (s)
@ -37,6 +37,11 @@ contains
! nfqso Target signal frequency (Hz) ! nfqso Target signal frequency (Hz)
! ntol Search range around nfqso (Hz) ! ntol Search range around nfqso (Hz)
! ndepth Optional decoding level ! ndepth Optional decoding level
! lclearave Flag to clear the message-averaging arrays
! emedelay Sync search extended to cover EME delays
! nQSOprogress Auto-sequencing state for the present QSO
! ncontest Supported contest type
! lapcqonly Flag to use AP only for CQ calls
! Output: sent to the callback routine for display to user ! Output: sent to the callback routine for display to user
use timer_module, only: timer use timer_module, only: timer
@ -61,6 +66,7 @@ contains
complex, allocatable :: c00(:) !Analytic signal, 6000 Sa/s complex, allocatable :: c00(:) !Analytic signal, 6000 Sa/s
complex, allocatable :: c0(:) !Analytic signal, 6000 Sa/s complex, allocatable :: c0(:) !Analytic signal, 6000 Sa/s
! Start by setting some parameters and allocating storage for large arrays
idec=-1 idec=-1
mode_q65=2**nsubmode mode_q65=2**nsubmode
npts=ntrperiod*12000 npts=ntrperiod*12000
@ -101,10 +107,13 @@ contains
dgen=0 dgen=0
call q65_enc(dgen,codewords) !Initialize the Q65 codec call q65_enc(dgen,codewords) !Initialize the Q65 codec
call timer('q65_dec0',0) call timer('q65_dec0',0)
call q65_dec0(nutc,iwave,ntrperiod, & ! Call top-level routine in q65 module: establish sync and try for a q3 decode.
nfqso,ntol,ndepth,lclearave,emedelay,xdt,f0,snr1,width,dat4, & call q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, &
snr2,idec) emedelay,xdt,f0,snr1,width,dat4,snr2,idec)
call timer('q65_dec0',1) call timer('q65_dec0',1)
print*,'AAA',idec
if(idec.ge.0) then if(idec.ge.0) then
xdt1=xdt !We have a list-decode result xdt1=xdt !We have a list-decode result
f1=f0 f1=f0
@ -166,7 +175,8 @@ contains
endif endif
100 decoded=' ' 100 decoded=' '
if(idec.gt.0) then print*,'BBB',idec
if(idec.ge.0) then
! ------------------------------------------------------ ! ------------------------------------------------------
! idec Meaning ! idec Meaning

View File

@ -20,17 +20,27 @@ contains
subroutine q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, & subroutine q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, &
emedelay,xdt,f0,snr1,width,dat4,snr2,idec) emedelay,xdt,f0,snr1,width,dat4,snr2,idec)
! Detect and align with the Q65 sync vector, returning time and frequency ! Top-level routine in q65 module
! offsets and SNR estimate.
! Input: iwave(0:nmax-1) Raw data ! Input: iwave(0:nmax-1) Raw data
! mode_q65 Tone spacing 1 2 4 8 16 (A-E) ! ntrperiod T/R sequence length (s)
! nsps Samples per symbol at 12000 Sa/s
! nfqso Target frequency (Hz) ! nfqso Target frequency (Hz)
! ntol Search range around nfqso (Hz) ! ntol Search range around nfqso (Hz)
! ndepth Requested decoding depth
! lclearave Flag to clear the accumulating array
! emedelay Extra delay for EME signals
! Output: xdt Time offset from nominal (s) ! Output: xdt Time offset from nominal (s)
! f0 Frequency of sync tone ! f0 Frequency of sync tone
! snr1 Relative SNR of sync signal ! snr1 Relative SNR of sync signal
! width Estimated Doppler spread
! dat4(13) Decoded message as 13 six-bit integers
! snr2 Estimated SNR of decoded signal
! idec Flag for decing results
! -1 No decode
! 0 No AP
! 1 "CQ ? ?"
! 2 "Mycall ? ?"
! 3 "MyCall HisCall ?"
use packjt77 use packjt77
use timer_module, only: timer use timer_module, only: timer
@ -48,7 +58,9 @@ subroutine q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, &
data first/.true./ data first/.true./
save first save first
if(nutc+ndepth.eq.-999) stop if(nutc+ndepth.eq.-999) stop !Silence compiler warnings
! Set seom parameters and allocate storage for large arrays
irc=-2 irc=-2
idec=-1 idec=-1
snr1=0. snr1=0.
@ -65,7 +77,12 @@ subroutine q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, &
ia2=max(ia,10*mode_q65,nint(100.0/df)) ia2=max(ia,10*mode_q65,nint(100.0/df))
nsmo=int(0.7*mode_q65*mode_q65) nsmo=int(0.7*mode_q65*mode_q65)
if(nsmo.lt.1) nsmo=1 if(nsmo.lt.1) nsmo=1
! nsmo=1 !### TEMPORARY ### if(first) then !Generate the sync vector
sync=-22.0/63.0 !Sync tone OFF
do k=1,22
sync(isync(k))=1.0 !Sync tone ON
enddo
endif
allocate(s1(iz,jz)) allocate(s1(iz,jz))
allocate(s3(-64:LL-65,63)) allocate(s3(-64:LL-65,63))
@ -79,17 +96,16 @@ subroutine q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, &
navg=0 navg=0
LL0=LL LL0=LL
endif endif
dtstep=nsps/(NSTEP*12000.0) !Step size in seconds
lag1=-1.0/dtstep
lag2=1.0/dtstep + 0.9999
if(nsps.ge.3600 .and. emedelay.gt.0) lag2=4.0/dtstep + 0.9999 !Include EME
j0=0.5/dtstep
if(nsps.ge.7200) j0=1.0/dtstep !Nominal start-signal index
s3=0. s3=0.
if(first) then !Generate the sync vector
sync=-22.0/63.0 !Sync tone OFF
do k=1,22
sync(isync(k))=1.0 !Sync tone ON
enddo
endif
call timer('s1 ',0) call timer('s1 ',0)
! Compute spectra with symbol length and NSTEP time bins per symbol. ! Compute symbol spectra with NSTEP time bins per symbol
call q65_symspec(iwave,ntrperiod*12000,iz,jz,s1) call q65_symspec(iwave,ntrperiod*12000,iz,jz,s1)
call timer('s1 ',1) call timer('s1 ',1)
@ -98,33 +114,25 @@ subroutine q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, &
call pctile(s1(i0-64:i0-65+LL,1:jz),LL*jz,40,base) call pctile(s1(i0-64:i0-65+LL,1:jz),LL*jz,40,base)
s1=s1/base s1=s1/base
! Apply fast AGC ! Apply fast AGC to the symbol spectra
s1max=20.0 !Empirical choice s1max=20.0 !Empirical choice
do j=1,jz !### Maybe wrong way? ### do j=1,jz !### Maybe wrong way? ###
smax=maxval(s1(i0-64:i0-65+LL,j)) smax=maxval(s1(i0-64:i0-65+LL,j))
if(smax.gt.s1max) s1(i0-64:i0-65+LL,j)=s1(i0-64:i0-65+LL,j)*s1max/smax if(smax.gt.s1max) s1(i0-64:i0-65+LL,j)=s1(i0-64:i0-65+LL,j)*s1max/smax
enddo enddo
dtstep=nsps/(NSTEP*12000.0) !Step size in seconds
lag1=-1.0/dtstep
lag2=1.0/dtstep + 0.9999
if(nsps.ge.3600 .and. emedelay.gt.0) lag2=4.0/dtstep + 0.9999 !Include EME
j0=0.5/dtstep
if(nsps.ge.7200) j0=1.0/dtstep !Nominal start-signal index
idec=-1
dat4=0 dat4=0
if(ncw.gt.0) then if(ncw.gt.0) then
! Try list decoding via "Deep Likelihood". ! Try list decoding via "Deep Likelihood".
call timer('ccf_85 ',0) call timer('ccf_85 ',0)
! Try to synchronize using all 85 symbols
call q65_ccf_85(s1,iz,jz,nfqso,ia,ia2,ipk,jpk,f0,xdt,imsg_best,ccf,ccf1) call q65_ccf_85(s1,iz,jz,nfqso,ia,ia2,ipk,jpk,f0,xdt,imsg_best,ccf,ccf1)
call timer('ccf_85 ',1) call timer('ccf_85 ',1)
call timer('list_dec',0) call timer('list_dec',0)
call q65_dec_q3(s1,iz,jz,s3,LL,ipk,jpk,snr2,dat4,idec,decoded) call q65_dec_q3(s1,iz,jz,s3,LL,ipk,jpk,snr2,dat4,idec,decoded)
call timer('list_dec',1) call timer('list_dec',1)
if(idec.ne.0) then
ic=ia2/4; ic=ia2/4;
base=(sum(ccf1(-ia2:-ia2+ic)) + sum(ccf1(ia2-ic:ia2)))/(2.0+2.0*ic); base=(sum(ccf1(-ia2:-ia2+ic)) + sum(ccf1(ia2-ic:ia2)))/(2.0+2.0*ic);
ccf1=ccf1-base ccf1=ccf1-base
@ -135,6 +143,7 @@ subroutine q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, &
smax=maxval(ccf2) smax=maxval(ccf2)
if(smax.gt.10.0) ccf2=10.0*ccf2/smax if(smax.gt.10.0) ccf2=10.0*ccf2/smax
endif endif
endif
! Get 2d CCF and ccf2 using sync symbols only ! Get 2d CCF and ccf2 using sync symbols only
call q65_ccf_22(s1,iz,jz,nfqso,ia,ia2,ipk,jpk,f0,xdt,ccf,ccf2) call q65_ccf_22(s1,iz,jz,nfqso,ia,ia2,ipk,jpk,f0,xdt,ccf,ccf2)
@ -158,7 +167,8 @@ subroutine q65_dec0(nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave, &
if(snr1.gt.10.0) ccf2=(10.0/snr1)*ccf2 if(snr1.gt.10.0) ccf2=(10.0/snr1)*ccf2
if(idec.le.0) then if(idec.le.0) then
! The q3 decode attempt failed, so we'll try a more general decode. ! The q3 decode attempt failed. Copy synchronied symbol spectra from s1
! into s3 and prepare to try a more general decode.
ccf1=ccf(:,jpk)/rms ccf1=ccf(:,jpk)/rms
if(snr1.gt.10.0) ccf1=(10.0/snr1)*ccf1 if(snr1.gt.10.0) ccf1=(10.0/snr1)*ccf1
call q65_s1_to_s3(s1,iz,jz,ipk,jpk,LL,mode_q65,sync,s3) call q65_s1_to_s3(s1,iz,jz,ipk,jpk,LL,mode_q65,sync,s3)
@ -264,7 +274,7 @@ subroutine q65_dec_q3(s1,iz,jz,s3,LL,ipk,jpk,snr2,dat4,idec,decoded)
call q65_dec1(s3,nsubmode,b90ts,esnodb,irc,dat4,decoded) call q65_dec1(s3,nsubmode,b90ts,esnodb,irc,dat4,decoded)
if(irc.ge.0) then if(irc.ge.0) then
snr2=esnodb - db(2500.0/baud) + 3.0 !Empirical adjustment snr2=esnodb - db(2500.0/baud) + 3.0 !Empirical adjustment
idec=1 idec=3
exit exit
endif endif
enddo enddo

View File

@ -78,7 +78,7 @@ subroutine q65_loops(c00,npts2,nsps2,nsubmode,ndepth,jpk0, &
! write(55,3055) ndepth,iaptype,idf,idt,ibw,ndist,irc,sum(s3(1:LL*NN)), & ! write(55,3055) ndepth,iaptype,idf,idt,ibw,ndist,irc,sum(s3(1:LL*NN)), &
! trim(decoded) ! trim(decoded)
!3055 format(7i4,f10.1,1x,a) !3055 format(7i4,f10.1,1x,a)
idec=iaptype+2 idec=iaptype
snr2=esnodb - db(2500.0/baud) snr2=esnodb - db(2500.0/baud)
xdt1=xdt0 + nsps2*ndt/(16.0*6000.0) xdt1=xdt0 + nsps2*ndt/(16.0*6000.0)
f1=f0 + 0.5*baud*ndf f1=f0 + 0.5*baud*ndf