mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2024-11-24 21:28:41 -05:00
First working multi-decode procedure for Q65.
This commit is contained in:
parent
86ada8c9d4
commit
72a4158898
@ -1,16 +1,16 @@
|
||||
subroutine ana64(dd,npts,c0)
|
||||
subroutine ana64(iwave,npts,c0)
|
||||
|
||||
use timer_module, only: timer
|
||||
|
||||
real dd(npts) !Raw data at 12000 Hz
|
||||
integer*2 iwave(npts) !Raw data at 12000 Hz
|
||||
complex c0(0:npts-1) !Complex data at 6000 Hz
|
||||
save
|
||||
|
||||
nfft1=npts
|
||||
nfft2=nfft1/2
|
||||
df1=12000.0/nfft1
|
||||
fac=2.0/nfft1
|
||||
c0(0:npts-1)=fac*dd(1:npts)
|
||||
fac=2.0/(32767.0*nfft1)
|
||||
c0(0:npts-1)=fac*iwave(1:npts)
|
||||
call four2a(c0,nfft1,1,-1,1) !Forward c2c FFT
|
||||
c0(nfft2/2+1:nfft2-1)=0.
|
||||
c0(0)=0.5*c0(0)
|
||||
|
@ -144,9 +144,7 @@ contains
|
||||
jpk0=(xdt+1.0)*6000 !Index of nominal start of signal
|
||||
if(ntrperiod.le.30) jpk0=(xdt+0.5)*6000 !For shortest sequences
|
||||
if(jpk0.lt.0) jpk0=0
|
||||
fac=1.0/32767.0
|
||||
dd=fac*iwave(1:npts)
|
||||
call ana64(dd,npts,c00) !Convert to complex c00() at 6000 Sa/s
|
||||
call ana64(iwave,npts,c00) !Convert to complex c00() at 6000 Sa/s
|
||||
call ft8apset(mycall,hiscall,ncontest,apsym0,aph10) ! Generate ap symbols
|
||||
where(apsym0.eq.-1) apsym0=0
|
||||
|
||||
@ -262,10 +260,78 @@ contains
|
||||
endif
|
||||
navg0=1000*navg(0) + navg(1)
|
||||
|
||||
! do icand=1,ncand
|
||||
! write(72,3072) icand,candidates(icand,1:3)
|
||||
!3072 format(i2,3f10.3)
|
||||
! enddo
|
||||
do icand=1,ncand
|
||||
! Prepare for single-period candidate decodes with iaptype = 0, 1, 2, or 4
|
||||
snr1=candidates(icand,1)
|
||||
xdt= candidates(icand,2)
|
||||
f0 = candidates(icand,3)
|
||||
jpk0=(xdt+1.0)*6000 !Index of nominal start of signal
|
||||
if(ntrperiod.le.30) jpk0=(xdt+0.5)*6000 !For shortest sequences
|
||||
if(jpk0.lt.0) jpk0=0
|
||||
call ana64(iwave,npts,c00) !Convert to complex c00() at 6000 Sa/s
|
||||
call ft8apset(mycall,hiscall,ncontest,apsym0,aph10) ! Generate ap symbols
|
||||
where(apsym0.eq.-1) apsym0=0
|
||||
|
||||
npasses=2
|
||||
if(nQSOprogress.eq.5) npasses=3
|
||||
if(lapcqonly) npasses=1
|
||||
iaptype=0
|
||||
do ipass=0,npasses !Loop over AP passes
|
||||
apmask=0 !Try first with no AP information
|
||||
apsymbols=0
|
||||
if(ipass.ge.1) then
|
||||
! Subsequent passes use AP information appropiate for nQSOprogress
|
||||
call q65_ap(nQSOprogress,ipass,ncontest,lapcqonly,iaptype, &
|
||||
apsym0,apmask1,apsymbols1)
|
||||
write(c78,1050) apmask1
|
||||
read(c78,1060) apmask
|
||||
write(c78,1050) apsymbols1
|
||||
read(c78,1060) apsymbols
|
||||
endif
|
||||
|
||||
call timer('q65loops',0)
|
||||
call q65_loops(c00,npts/2,nsps/2,nsubmode,ndepth,jpk0, &
|
||||
xdt,f0,iaptype,xdt1,f1,snr2,dat4,idec)
|
||||
! idec=-1 !### TEMPORARY ###
|
||||
call timer('q65loops',1)
|
||||
if(idec.ge.0) then
|
||||
dtdec=xdt1
|
||||
f0dec=f1
|
||||
go to 200 !Successful decode, we're done
|
||||
endif
|
||||
enddo ! ipass
|
||||
|
||||
200 decoded=' '
|
||||
if(idec.ge.0) then
|
||||
! Unpack decoded message for display to user
|
||||
write(c77,1000) dat4(1:12),dat4(13)/2
|
||||
call unpack77(c77,0,decoded,unpk77_success) !Unpack to get msgsent
|
||||
nsnr=nint(snr2)
|
||||
call this%callback(nutc,snr1,nsnr,dtdec,f0dec,decoded, &
|
||||
idec,nused,ntrperiod)
|
||||
if(iand(ndepth,128).ne.0) call q65_clravg !AutoClrAvg after decode
|
||||
call sec0(1,tdecode)
|
||||
open(22,file=trim(data_dir)//'/q65_decodes.dat',status='unknown', &
|
||||
position='append',iostat=ios)
|
||||
if(ios.eq.0) then
|
||||
! Save decoding parameters to q65_decoded.dat, for later analysis.
|
||||
c6=hiscall(1:6)
|
||||
if(c6.eq.' ') c6='<b> '
|
||||
c4=hisgrid(1:4)
|
||||
if(c4.eq.' ') c4='<b> '
|
||||
if(ntrperiod.ge.60) then
|
||||
write(22,1022) nutc,ntrperiod,nsubmode,nQSOprogress,idec, &
|
||||
nused,iaptype,irc,idf,idt,ibw,xdt,f0,snr1,snr2, &
|
||||
tdecode,mycall(1:6),c6,c4,trim(decoded)
|
||||
else
|
||||
write(22,1023) nutc,ntrperiod,nsubmode,nQSOprogress,idec, &
|
||||
nused,iaptype,irc,idf,idt,ibw,xdt,f0,snr1,snr2, &
|
||||
tdecode,mycall(1:6),c6,c4,trim(decoded)
|
||||
endif
|
||||
close(22)
|
||||
endif
|
||||
endif
|
||||
enddo
|
||||
|
||||
return
|
||||
end subroutine decode
|
||||
|
@ -446,10 +446,12 @@ subroutine q65_ccf_22(s1,iz,jz,nfqso,ipk,jpk,f0,xdt,ccf2)
|
||||
do j=1,20
|
||||
i=indx(jzz-j+1)+i1-1
|
||||
if(ccf2(i).lt.3.0) exit
|
||||
f=i*df
|
||||
if(f.ge.(nfqso-ftol) .and. f.le.(nfqso+ftol)) cycle
|
||||
ncand=ncand+1
|
||||
candidates(ncand,1)=ccf2(i)
|
||||
candidates(ncand,2)=xdt2(i)
|
||||
candidates(ncand,3)=i*df
|
||||
candidates(ncand,3)=f
|
||||
enddo
|
||||
|
||||
return
|
||||
|
128
lib/qra64a.f90
128
lib/qra64a.f90
@ -1,128 +0,0 @@
|
||||
subroutine qra64a(dd,npts,nf1,nf2,nfqso,ntol,mode64,minsync,ndepth, &
|
||||
emedelay,mycall_12,hiscall_12,hisgrid_6,sync,nsnr,dtx,nfreq,decoded,nft)
|
||||
|
||||
use packjt
|
||||
use timer_module, only: timer
|
||||
|
||||
parameter (NMAX=60*12000,LN=1152*63)
|
||||
character decoded*22
|
||||
character*12 mycall_12,hiscall_12
|
||||
character*6 mycall,hiscall,hisgrid_6
|
||||
character*4 hisgrid
|
||||
logical ltext
|
||||
complex c00(0:720000) !Analytic signal for dd()
|
||||
real dd(NMAX) !Raw data sampled at 12000 Hz
|
||||
integer dat4(12) !Decoded message (as 12 integers)
|
||||
data nc1z/-1/,nc2z/-1/,ng2z/-1/,maxaptypez/-1/
|
||||
save
|
||||
|
||||
call timer('qra64a ',0)
|
||||
irc=-1
|
||||
decoded=' '
|
||||
nft=99
|
||||
if(nfqso.lt.nf1 .or. nfqso.gt.nf2) go to 900
|
||||
|
||||
mycall=mycall_12(1:6) !### May need fixing? ###
|
||||
hiscall=hiscall_12(1:6)
|
||||
hisgrid=hisgrid_6(1:4)
|
||||
call packcall(mycall,nc1,ltext)
|
||||
call packcall(hiscall,nc2,ltext)
|
||||
call packgrid(hisgrid,ng2,ltext)
|
||||
nSubmode=0
|
||||
if(mode64.eq.2) nSubmode=1
|
||||
if(mode64.eq.4) nSubmode=2
|
||||
if(mode64.eq.8) nSubmode=3
|
||||
if(mode64.eq.16) nSubmode=4
|
||||
b90=1.0
|
||||
nFadingModel=1
|
||||
maxaptype=4
|
||||
if(iand(ndepth,64).ne.0) maxaptype=5
|
||||
call qra_params(ndepth,maxaptype,idfmax,idtmax,ibwmin,ibwmax,maxdist)
|
||||
if(nc1.ne.nc1z .or. nc2.ne.nc2z .or. ng2.ne.ng2z .or. &
|
||||
maxaptype.ne.maxaptypez) then
|
||||
do naptype=0,maxaptype
|
||||
if(naptype.eq.2 .and. maxaptype.eq.4) cycle
|
||||
call qra64_dec(s3dummy,nc1,nc2,ng2,naptype,1,nSubmode,b90, &
|
||||
nFadingModel,dat4,snr2,irc)
|
||||
enddo
|
||||
nc1z=nc1
|
||||
nc2z=nc2
|
||||
ng2z=ng2
|
||||
maxaptypez=maxaptype
|
||||
endif
|
||||
naptype=maxaptype
|
||||
|
||||
call ana64(dd,npts,c00)
|
||||
|
||||
call timer('sync64 ',0)
|
||||
call sync64(c00,nf1,nf2,nfqso,ntol,minsync,mode64,emedelay,dtx,f0, &
|
||||
jpk0,sync,sync2,width)
|
||||
call timer('sync64 ',1)
|
||||
nfreq=nint(f0)
|
||||
if(mode64.eq.1 .and. minsync.ne.-1 .and. (sync-7.0).lt.minsync) go to 900
|
||||
|
||||
nsps=6912
|
||||
call timer('qraloops',0)
|
||||
call qra_loops(c00,npts/2,nsps,64,mode64,nsubmode,nFadingModel, &
|
||||
ndepth,nc1,nc2,ng2,naptype,jpk0,dtx,f0,width,snr2,irc,dat4)
|
||||
call timer('qraloops',1)
|
||||
|
||||
decoded=' '
|
||||
if(irc.ge.0) then
|
||||
call unpackmsg(dat4,decoded) !Unpack the user message
|
||||
call fmtmsg(decoded,iz)
|
||||
if(index(decoded,"000AAA ").ge.1) then
|
||||
! Suppress a certain type of garbage decode.
|
||||
decoded=' '
|
||||
irc=-1
|
||||
endif
|
||||
nft=100 + irc
|
||||
nsnr=nint(snr2)
|
||||
else
|
||||
snr2=0.
|
||||
endif
|
||||
nfreq=nint(f0)
|
||||
|
||||
900 if(irc.lt.0) then
|
||||
sy=max(1.0,sync)
|
||||
if(nSubmode.eq.0) nsnr=nint(10.0*log10(sy)-35.0) !A
|
||||
if(nSubmode.eq.1) nsnr=nint(10.0*log10(sy)-34.0) !B
|
||||
if(nSubmode.eq.2) nsnr=nint(10.0*log10(sy)-29.0) !C
|
||||
if(nSubmode.eq.3) nsnr=nint(10.0*log10(sy)-29.0) !D
|
||||
if(nSubmode.eq.4) nsnr=nint(10.0*log10(sy)-24.0) !E
|
||||
endif
|
||||
call timer('qra64a ',1)
|
||||
|
||||
return
|
||||
end subroutine qra64a
|
||||
|
||||
subroutine qra_params(ndepth,maxaptype,idf0max,idt0max,ibwmin,ibwmax,maxdist)
|
||||
|
||||
! If file qra_params is present in CWD, read decoding params from it.
|
||||
|
||||
integer iparam(7)
|
||||
logical first,ex
|
||||
! data iparam/3,5,11,11,0,11,60/ !Maximum effort
|
||||
data iparam/3,5,7,7,0,4,15/ !Default values
|
||||
data first/.true./
|
||||
save first,iparam
|
||||
|
||||
if(first) then
|
||||
inquire(file='qra_params',exist=ex)
|
||||
if(ex) then
|
||||
open(29,file='qra_params',status='old')
|
||||
read(29,*) iparam
|
||||
close(29)
|
||||
endif
|
||||
first=.false.
|
||||
endif
|
||||
ndepth=iparam(1)
|
||||
maxaptype=iparam(2)
|
||||
idf0max=iparam(3)
|
||||
idt0max=iparam(4)
|
||||
ibwmin=iparam(5)
|
||||
ibwmax=iparam(6)
|
||||
maxdist=iparam(7)
|
||||
|
||||
return
|
||||
end subroutine qra_params
|
Loading…
Reference in New Issue
Block a user