More progress on q3list decodes in NA VHF contest mode, Q65-60A.

This commit is contained in:
Joe Taylor 2023-02-12 17:33:21 -05:00
parent 871198c44f
commit 7bf6a6123d
4 changed files with 71 additions and 10 deletions

View File

@ -45,6 +45,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
real ss(184,NSMAX) real ss(184,NSMAX)
logical baddata,newdat65,newdat9,single_decode,bVHF,bad0,newdat,ex logical baddata,newdat65,newdat9,single_decode,bVHF,bad0,newdat,ex
integer*2 id2(NTMAX*12000) integer*2 id2(NTMAX*12000)
integer nqf(20)
type(params_block) :: params type(params_block) :: params
real*4 dd(NTMAX*12000) real*4 dd(NTMAX*12000)
character(len=20) :: datetime character(len=20) :: datetime
@ -211,7 +212,22 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
params%nfa,params%nfb,logical(params%nclearave), & params%nfa,params%nfb,logical(params%nclearave), &
single_decode,logical(params%nagain),params%max_drift, & single_decode,logical(params%nagain),params%max_drift, &
logical(params%newdat),params%emedelay,mycall,hiscall,hisgrid, & logical(params%newdat),params%emedelay,mycall,hiscall,hisgrid, &
params%nQSOProgress,ncontest,logical(params%lapcqonly),navg0) params%nQSOProgress,ncontest,logical(params%lapcqonly),navg0,nqf)
!###
do k=1,20
if(nqf(k).eq.0) exit
nqd=1
navg0=0
ntol=5
call my_q65%decode(q65_decoded,id2,nqd,params%nutc,params%ntr, &
params%nsubmode,nqf(k),ntol,params%ndepth, &
params%nfa,params%nfb,logical(params%nclearave), &
.true.,.true.,params%max_drift, &
.false.,params%emedelay,mycall,hiscall,hisgrid, &
params%nQSOProgress,ncontest,logical(params%lapcqonly),navg0,nqf)
enddo
!###
call timer('dec_q65 ',1) call timer('dec_q65 ',1)
close(17) close(17)
go to 800 go to 800

View File

@ -14,6 +14,7 @@ subroutine map65_mmdec(nutc,id2,nqd,nsubmode,nfa,nfb,nfqso,ntol,newdat, &
logical single_decode,bVHF,lnewdat,lagain,lclearave,lapcqonly logical single_decode,bVHF,lnewdat,lagain,lclearave,lapcqonly
integer*2 id2(300*12000) integer*2 id2(300*12000)
integer nqf(20)
! type(params_block) :: params ! type(params_block) :: params
character(len=12) :: mycall, hiscall character(len=12) :: mycall, hiscall
character(len=6) :: hisgrid character(len=6) :: hisgrid
@ -43,7 +44,7 @@ subroutine map65_mmdec(nutc,id2,nqd,nsubmode,nfa,nfb,nfqso,ntol,newdat, &
call timer('dec_q65 ',0) call timer('dec_q65 ',0)
call my_q65%decode(q65_decoded,id2,nqd,nutc,ntrperiod,nsubmode,nfqso, & call my_q65%decode(q65_decoded,id2,nqd,nutc,ntrperiod,nsubmode,nfqso, &
ntol,ndepth,nfa,nfb,lclearave,single_decode,lagain,max_drift,lnewdat, & ntol,ndepth,nfa,nfb,lclearave,single_decode,lagain,max_drift,lnewdat, &
emedelay,mycall,hiscall,hisgrid,nQSOProgress,ncontest,lapcqonly,navg0) emedelay,mycall,hiscall,hisgrid,nQSOProgress,ncontest,lapcqonly,navg0,nqf)
call timer('dec_q65 ',1) call timer('dec_q65 ',1)
return return

View File

@ -33,7 +33,7 @@ contains
subroutine decode(this,callback,iwave,nqd0,nutc,ntrperiod,nsubmode,nfqso, & subroutine decode(this,callback,iwave,nqd0,nutc,ntrperiod,nsubmode,nfqso, &
ntol,ndepth,nfa0,nfb0,lclearave,single_decode,lagain,max_drift0, & ntol,ndepth,nfa0,nfb0,lclearave,single_decode,lagain,max_drift0, &
lnewdat0,emedelay,mycall,hiscall,hisgrid,nQSOprogress,ncontest, & lnewdat0,emedelay,mycall,hiscall,hisgrid,nQSOprogress,ncontest, &
lapcqonly,navg0) lapcqonly,navg0,nqf)
! Top-level routine that organizes the decoding of Q65 signals ! Top-level routine that organizes the decoding of Q65 signals
! Input: iwave Raw data, i*2 ! Input: iwave Raw data, i*2
@ -74,14 +74,15 @@ contains
character*80 fmt character*80 fmt
integer*2 iwave(NMAX) !Raw data integer*2 iwave(NMAX) !Raw data
real, allocatable :: dd(:) !Raw data real, allocatable :: dd(:) !Raw data
real xdtdecodes(100)
real f0decodes(100) real f0decodes(100)
integer dat4(13) !Decoded message as 12 6-bit integers integer dat4(13) !Decoded message as 12 6-bit integers
integer dgen(13) integer dgen(13)
integer nq65param(3) integer nqf(20)
integer stageno !Added by W3SZ integer stageno !Added by W3SZ
integer time integer time
logical lclearave,lnewdat0,lapcqonly,unpk77_success logical lclearave,lnewdat0,lapcqonly,unpk77_success
logical single_decode,lagain,ex logical single_decode,lagain
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
type(q3list) callers(MAX_CALLERS) type(q3list) callers(MAX_CALLERS)
@ -92,6 +93,7 @@ contains
ndecodes=0 ndecodes=0
decodes=' ' decodes=' '
f0decodes=0. f0decodes=0.
xdtdecodes=0.
nfa=nfa0 nfa=nfa0
nfb=nfb0 nfb=nfb0
nqd=nqd0 nqd=nqd0
@ -183,7 +185,7 @@ contains
if(ichar(hiscall(1:1)).eq.0) hiscall=' ' if(ichar(hiscall(1:1)).eq.0) hiscall=' '
if(ichar(hisgrid(1:1)).eq.0) hisgrid=' ' if(ichar(hisgrid(1:1)).eq.0) hisgrid=' '
ncw=0 ncw=0
if(nqd.eq.1 .or. lagain) then if(nqd.eq.1 .or. lagain .or. ncontest.eq.1) then
if(ncontest.eq.1) then if(ncontest.eq.1) then
call q65_set_list2(mycall,hiscall,hisgrid,callers,nhist2, & call q65_set_list2(mycall,hiscall,hisgrid,callers,nhist2, &
codewords,ncw) codewords,ncw)
@ -214,6 +216,7 @@ contains
f0dec=f0 f0dec=f0
go to 100 go to 100
endif endif
if(ncontest.eq.1 .and. lagain) go to 100
! Prepare for a single-period decode with iaptype = 0, 1, 2, or 4 ! Prepare for a single-period decode with iaptype = 0, 1, 2, or 4
jpk0=(xdt+1.0)*6000 !Index of nominal start of signal jpk0=(xdt+1.0)*6000 !Index of nominal start of signal
@ -318,6 +321,7 @@ contains
ndecodes=min(ndecodes+1,100) ndecodes=min(ndecodes+1,100)
decodes(ndecodes)=decoded decodes(ndecodes)=decoded
f0decodes(ndecodes)=f0dec f0decodes(ndecodes)=f0dec
xdtdecodes(ndecodes)=dtdec
call q65_snr(dat4,dtdec,f0dec,mode_q65,snr2) call q65_snr(dat4,dtdec,f0dec,mode_q65,snr2)
nsnr=nint(snr2) nsnr=nint(snr2)
call this%callback(nutc,snr1,nsnr,dtdec,f0dec,decoded, & call this%callback(nutc,snr1,nsnr,dtdec,f0dec,decoded, &
@ -363,6 +367,24 @@ contains
fdiff=f0-f0decodes(i) fdiff=f0-f0decodes(i)
if(fdiff.gt.-baud*mode_q65 .and. fdiff.lt.65*baud*mode_q65) go to 800 if(fdiff.gt.-baud*mode_q65 .and. fdiff.lt.65*baud*mode_q65) go to 800
enddo enddo
!### TEST REGION
if(ncontest.eq.-1) then
call timer('q65_dec0',0)
! Call top-level routine in q65 module: establish sync and try for a
! q3 or q0 decode.
call q65_dec0(iavg,iwave,ntrperiod,nint(f0),ntol,lclearave, &
emedelay,xdt,f0,snr1,width,dat4,snr2,idec,stageno)
call timer('q65_dec0',1)
write(*,3001) icand,nint(f0),xdt,idec
3001 format('a',i3,i5,f6.1,i3)
if(idec.ge.0) then
dtdec=xdt !We have a q3 or q0 decode at f0
f0dec=f0
go to 200
endif
endif
!###
jpk0=(xdt+1.0)*6000 !Index of nominal start of signal jpk0=(xdt+1.0)*6000 !Index of nominal start of signal
if(ntrperiod.le.30) jpk0=(xdt+0.5)*6000 !For shortest sequences if(ntrperiod.le.30) jpk0=(xdt+0.5)*6000 !For shortest sequences
if(jpk0.lt.0) jpk0=0 if(jpk0.lt.0) jpk0=0
@ -452,9 +474,31 @@ contains
800 continue 800 continue
enddo ! icand enddo ! icand
if(iavg.eq.0 .and.navg(iseq).ge.2 .and. iand(ndepth,16).ne.0) go to 50 if(iavg.eq.0 .and.navg(iseq).ge.2 .and. iand(ndepth,16).ne.0) go to 50
900 close(24) 900 close(24)
return
if(ncontest.ne.1 .or. lagain) go to 999
if(ntrperiod.ne.60 .or. nsubmode.ne.0) go to 999
! This is first time here, and we're running Q65-60A in NA VHF Contest mode.
! Return a list of potential sync frequencies at which to try q3 decoding.
k=0
nqf=0
bw=baud*mode_q65*65
do i=1,ncand
! snr1=candidates(i,1)
! xdt= candidates(i,2)
f0 = candidates(i,3)
do j=1,ndecodes ! Already decoded one at or near this frequency?
fj=f0decodes(j)
if(f0.gt.fj-5.0 .and. f0.lt.fj+bw+5.0) go to 990
enddo
k=k+1
nqf(k)=nint(f0)
990 continue
enddo
999 return
end subroutine decode end subroutine decode
end module q65_decode end module q65_decode