New short ping decoding algorithm for msk144 realtime decoder. Not yet enabled.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@7108 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
Steven Franke 2016-09-23 22:28:11 +00:00
parent 9831fb9cfc
commit 3df371f11b
6 changed files with 79 additions and 192 deletions

View File

@ -87,7 +87,7 @@ subroutine msk144decodeframe(c,msgreceived,nsuccess)
ssig=sqrt(s2av-sav*sav) ssig=sqrt(s2av-sav*sav)
softbits=softbits/ssig softbits=softbits/ssig
sigma=0.70 sigma=0.72
llr(1:48)=softbits(9:9+47) llr(1:48)=softbits(9:9+47)
llr(49:128)=softbits(65:65+80-1) llr(49:128)=softbits(65:65+80-1)
llr=2.0*llr/(sigma*sigma) llr=2.0*llr/(sigma*sigma)

View File

@ -1,47 +1,43 @@
subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fret,snrret,tret) subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fc,fret,tret)
! msk144 short-ping-decoder ! msk144 short-ping-decoder
use timer_module, only: timer use timer_module, only: timer
parameter (NSPM=864, NPTS=3*NSPM, MAXSTEPS=1700, NFFT=NSPM, MAXCAND=5) parameter (NSPM=864, MAXSTEPS=100, NFFT=NSPM, MAXCAND=5, NPATTERNS=6)
character*22 msgreceived character*22 msgreceived
complex cbig(n) complex cbig(n)
complex cdat(NPTS) !Analytic signal complex cdat(3*NSPM) !Analytic signal
complex cdat2(NPTS)
complex c(NSPM) complex c(NSPM)
complex ct(NSPM)
complex ctmp(NFFT) complex ctmp(NFFT)
complex cb(42) !Complex waveform for sync word
complex cbr(42) !Complex waveform for reversed sync word
complex cfac,cca,ccb
complex cc(NPTS)
complex ccr(NPTS)
complex cc1(NPTS)
complex cc2(NPTS)
complex ccr1(NPTS)
complex ccr2(NPTS)
complex bb(6)
integer s8(8),s8r(8)
integer, dimension(1) :: iloc integer, dimension(1) :: iloc
integer indices(MAXSTEPS) integer indices(MAXSTEPS)
integer ipeaks(10) integer npkloc(10)
integer navpatterns(3,NPATTERNS)
integer navmask(3)
integer nstart(MAXCAND)
logical ismask(NFFT) logical ismask(NFFT)
real cbi(42),cbq(42)
real detmet(-2:MAXSTEPS+3) real detmet(-2:MAXSTEPS+3)
real detmet2(-2:MAXSTEPS+3) real detmet2(-2:MAXSTEPS+3)
real detfer(MAXSTEPS) real detfer(MAXSTEPS)
real rcw(12) real rcw(12)
real dd(NPTS)
real ferrs(MAXCAND) real ferrs(MAXCAND)
real pp(12) !Half-sine pulse shape
real snrs(MAXCAND) real snrs(MAXCAND)
real times(MAXCAND)
real tonespec(NFFT) real tonespec(NFFT)
real tpat(NPATTERNS)
real*8 dt, df, fs, pi, twopi real*8 dt, df, fs, pi, twopi
logical first logical first
data first/.true./ data first/.true./
data s8/0,1,1,1,0,0,1,0/ data navpatterns/ &
data s8r/1,0,1,1,0,0,0,1/ 0,1,0, &
save df,first,cb,fs,pi,twopi,dt,s8,rcw,pp,nmatchedfilter 1,0,0, &
0,0,1, &
1,1,0, &
0,1,1, &
1,1,1/
data tpat/1.5,0.5,2.5,1.0,2.0,1.5/
save df,first,fs,pi,twopi,dt,tframe,rcw
if(first) then if(first) then
nmatchedfilter=1 nmatchedfilter=1
@ -51,40 +47,19 @@ subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fret,snrret,tret)
fs=12000.0 fs=12000.0
dt=1.0/fs dt=1.0/fs
df=fs/NFFT df=fs/NFFT
tframe=NSPM/fs
do i=1,12 do i=1,12
angle=(i-1)*pi/12.0 angle=(i-1)*pi/12.0
pp(i)=sin(angle)
rcw(i)=(1-cos(angle))/2 rcw(i)=(1-cos(angle))/2
enddo enddo
! define the sync word waveforms
s8=2*s8-1
cbq(1:6)=pp(7:12)*s8(1)
cbq(7:18)=pp*s8(3)
cbq(19:30)=pp*s8(5)
cbq(31:42)=pp*s8(7)
cbi(1:12)=pp*s8(2)
cbi(13:24)=pp*s8(4)
cbi(25:36)=pp*s8(6)
cbi(37:42)=pp(1:6)*s8(8)
cb=cmplx(cbi,cbq)
s8r=2*s8r-1
cbq(1:6)=pp(7:12)*s8r(1)
cbq(7:18)=pp*s8r(3)
cbq(19:30)=pp*s8r(5)
cbq(31:42)=pp*s8r(7)
cbi(1:12)=pp*s8r(2)
cbi(13:24)=pp*s8r(4)
cbi(25:36)=pp*s8r(6)
cbi(37:42)=pp(1:6)*s8r(8)
cbr=cmplx(cbi,cbq)
first=.false. first=.false.
endif endif
! fill the detmet, detferr arrays ! fill the detmet, detferr arrays
nstep=(n-NPTS)/216 ! 72ms/4=18ms steps nstep=(n-NSPM)/216 ! 72ms/4=18ms steps
detmet=0 detmet=0
detmet2=0 detmet2=0
detfer=-999.99 detfer=-999.99
@ -148,15 +123,13 @@ subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fret,snrret,tret)
do ip=1,MAXCAND ! Find candidates do ip=1,MAXCAND ! Find candidates
iloc=maxloc(detmet(1:nstep)) iloc=maxloc(detmet(1:nstep))
il=iloc(1) il=iloc(1)
! if( (detmet(il) .lt. 4.0) ) exit
if( (detmet(il) .lt. 3.0) ) exit if( (detmet(il) .lt. 3.0) ) exit
if( abs(detfer(il)) .le. ntol ) then if( abs(detfer(il)) .le. ntol ) then
ndet=ndet+1 ndet=ndet+1
times(ndet)=((il-1)*216+NSPM/2)*dt nstart(ndet)=1+(il-1)*216+1
ferrs(ndet)=detfer(il) ferrs(ndet)=detfer(il)
snrs(ndet)=12.0*log10(detmet(il))/2-9.0 snrs(ndet)=12.0*log10(detmet(il))/2-9.0
endif endif
! detmet(max(1,il-1):min(nstep,il+1))=0.0
detmet(il)=0.0 detmet(il)=0.0
enddo enddo
@ -167,146 +140,53 @@ subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fret,snrret,tret)
if( (detmet2(il) .lt. 12.0) ) exit if( (detmet2(il) .lt. 12.0) ) exit
if( abs(detfer(il)) .le. ntol ) then if( abs(detfer(il)) .le. ntol ) then
ndet=ndet+1 ndet=ndet+1
times(ndet)=((il-1)*216+NSPM/2)*dt nstart(ndet)=1+(il-1)*216+1
ferrs(ndet)=detfer(il) ferrs(ndet)=detfer(il)
snrs(ndet)=12.0*log10(detmet2(il))/2-9.0 snrs(ndet)=12.0*log10(detmet2(il))/2-9.0
endif endif
! detmet2(max(1,il-1):min(nstep,il+1))=0.0
detmet2(il)=0.0 detmet2(il)=0.0
enddo enddo
endif endif
nsuccess=0 nsuccess=0
msgreceived=' ' msgreceived=' '
do ip=1,ndet ! Try to sync/demod/decode each candidate. npeaks=2
imid=times(ip)*fs ntol0=8
if( imid .lt. NPTS/2 ) imid=NPTS/2 ndf=2
if( imid .gt. n-NPTS/2 ) imid=n-NPTS/2 do icand=1,ndet ! Try to sync/demod/decode each candidate.
cdat=cbig(imid-NPTS/2+1:imid+NPTS/2) ib=max(1,nstart(icand)-NSPM)
ferr=ferrs(ip) ie=ib-1+3*NSPM
if( ie .gt. n ) then
ie=n
ib=ie-3*NSPM+1
endif
cdat=cbig(ib:ie)
fo=fc+ferrs(icand)
do iav=1,NPATTERNS
navmask=navpatterns(1:3,iav)
call msk144sync(cdat,3,ntol0,ndf,navmask,npeaks,fo,fest,npkloc,nsyncsuccess,c)
! remove coarse freq error - should now be within a few Hz if( nsyncsuccess .eq. 0 ) cycle
call tweak1(cdat,NPTS,-(1500+ferr),cdat)
! attempt frame synchronization
! correlate with sync word waveforms
cc=0
ccr=0
cc1=0
cc2=0
ccr1=0
ccr2=0
do i=1,NPTS-(56*6+41)
cc1(i)=sum(cdat(i:i+41)*conjg(cb))
cc2(i)=sum(cdat(i+56*6:i+56*6+41)*conjg(cb))
enddo
cc=cc1+cc2
dd=abs(cc1)*abs(cc2)
cmax=maxval(abs(cc))
! Find 6 largest peaks
do ipk=1, 6
iloc=maxloc(abs(cc))
ic1=iloc(1)
iloc=maxloc(dd)
ic2=iloc(1)
ipeaks(ipk)=ic2
dd(max(1,ic2-7):min(NPTS-56*6-41,ic2+7))=0.0
enddo
do ipk=1,4 do ipk=1,npeaks
do is=1,3
ic0=npkloc(ipk)
if( is.eq.2) ic0=max(1,ic0-1)
if( is.eq.3) ic0=min(NSPM,ic0+1)
ct=cshift(c,ic0-1)
call msk144decodeframe(ct,msgreceived,ndecodesuccess)
! we want ic to be the index of the first sample of the frame if( ndecodesuccess .gt. 0 ) then
ic0=ipeaks(ipk) tret=(nstart(icand)+NSPM/2)/fs
fret=fest
! fine adjustment of sync index !write(*,*) icand, iav, ipk, is, tret, fret, msgreceived
do i=1,6 nsuccess=1
if( ic0+11+NSPM .le. NPTS ) then return
bb(i) = sum( ( cdat(ic0+i-1+6:ic0+i-1+6+NSPM:6) * conjg( cdat(ic0+i-1:ic0+i-1+NSPM:6) ) )**2 ) endif
else enddo
bb(i) = sum( ( cdat(ic0+i-1+6:NPTS:6) * conjg( cdat(ic0+i-1:NPTS-6:6) ) )**2 )
endif
enddo enddo
iloc=maxloc(abs(bb)) enddo
ibb=iloc(1)
bba=abs(bb(ibb))
bbp=atan2(-imag(bb(ibb)),-real(bb(ibb)))/(2*twopi*6*dt)
if( ibb .le. 3 ) ibb=ibb-1
if( ibb .gt. 3 ) ibb=ibb-7
do id=1,3 ! Slicer dither.
if( id .eq. 1 ) is=0
if( id .eq. 2 ) is=-1
if( id .eq. 3 ) is=1
! Adjust frame index to place peak of bb at desired lag
ic=ic0+ibb+is
if( ic .lt. 1 ) ic=ic+864
! Estimate fine frequency error.
! Should a larger separation be used when frames are averaged?
cca=sum(cdat(ic:ic+41)*conjg(cb))
if( ic+56*6+41 .le. NPTS ) then
ccb=sum(cdat(ic+56*6:ic+56*6+41)*conjg(cb))
cfac=ccb*conjg(cca)
ferr2=atan2(imag(cfac),real(cfac))/(twopi*56*6*dt)
else
ccb=sum(cdat(ic-88*6:ic-88*6+41)*conjg(cb))
cfac=cca*conjg(ccb)
ferr2=atan2(imag(cfac),real(cfac))/(twopi*88*6*dt)
endif
! Final estimate of the carrier frequency - returned to the calling program
fest=1500+ferr+ferr2
do idf=0,4 ! frequency jitter
if( idf .eq. 0 ) then
deltaf=0.0
elseif( mod(idf,2) .eq. 0 ) then
deltaf=idf
else
deltaf=-(idf+1)
endif
! Remove fine frequency error
call tweak1(cdat,NPTS,-(ferr2+deltaf),cdat2)
! place the beginning of frame at index NSPM+1
cdat2=cshift(cdat2,ic-(NSPM+1))
do iav=1,8 ! Hopefully we can eliminate some of these after looking at more examples
if( iav .eq. 1 ) then
c=cdat2(NSPM+1:2*NSPM)
elseif( iav .eq. 2 ) then
c=cdat2(NSPM-431:NSPM+432)
c=cshift(c,-432)
elseif( iav .eq. 3 ) then
c=cdat2(2*NSPM-431:2*NSPM+432)
c=cshift(c,-432)
elseif( iav .eq. 4 ) then
c=cdat2(1:NSPM)
elseif( iav .eq. 5 ) then
c=cdat2(2*NSPM+1:NPTS)
elseif( iav .eq. 6 ) then
c=cdat2(1:NSPM)+cdat2(NSPM+1:2*NSPM)
elseif( iav .eq. 7 ) then
c=cdat2(NSPM+1:2*NSPM)+cdat2(2*NSPM+1:NPTS)
elseif( iav .eq. 8 ) then
c=cdat2(1:NSPM)+cdat2(NSPM+1:2*NSPM)+cdat2(2*NSPM+1:NPTS)
endif
call msk144decodeframe(c,msgreceived,nsuccess)
if( nsuccess .eq. 1 ) then
fret=1500+ferrs(ip)
snrret=snrs(ip)
tret=times(ip)
return
endif
enddo ! frame averaging loop
enddo ! frequency dithering loop
enddo ! sample-time dither loop
enddo ! peak loop
enddo ! candidate loop enddo ! candidate loop
return return
end subroutine msk144spd end subroutine msk144spd

View File

@ -1,8 +1,8 @@
subroutine msk144sync(cdat,n,ntol,ndf,navmask,npeaks,fest,npklocs,nsuccess,c) subroutine msk144sync(cdat,nframes,ntol,ndf,navmask,npeaks,fc,fest,npklocs,nsuccess,c)
parameter (NSPM=864) parameter (NSPM=864)
complex cdat(n) complex cdat(NSPM*nframes)
complex cdat2(n) complex cdat2(NSPM*nframes)
complex c(NSPM) !Coherently averaged complex data complex c(NSPM) !Coherently averaged complex data
complex ct2(2*NSPM) complex ct2(2*NSPM)
complex cs(NSPM) complex cs(NSPM)
@ -12,7 +12,7 @@ subroutine msk144sync(cdat,n,ntol,ndf,navmask,npeaks,fest,npklocs,nsuccess,c)
integer s8(8) integer s8(8)
integer iloc(1) integer iloc(1)
integer npklocs(npeaks) integer npklocs(npeaks)
integer navmask(8) ! defines which frames to average integer navmask(nframes) ! defines which frames to average
real cbi(42),cbq(42) real cbi(42),cbq(42)
real pkamps(npeaks) real pkamps(npeaks)
@ -54,11 +54,12 @@ subroutine msk144sync(cdat,n,ntol,ndf,navmask,npeaks,fest,npklocs,nsuccess,c)
navg=sum(navmask) navg=sum(navmask)
xmax=0.0 xmax=0.0
bestf=0.0 bestf=0.0
n=nframes*NSPM
do ifr=-ntol,ntol,ndf !Find freq that maximizes sync do ifr=-ntol,ntol,ndf !Find freq that maximizes sync
ferr=ifr ferr=ifr
call tweak1(cdat,n,-(1500+ferr),cdat2) call tweak1(cdat,n,-(fc+ferr),cdat2)
c=0 c=0
do i=1,8 do i=1,nframes
ib=(i-1)*NSPM+1 ib=(i-1)*NSPM+1
ie=ib+NSPM-1 ie=ib+NSPM-1
if( navmask(i) .eq. 1 ) then if( navmask(i) .eq. 1 ) then
@ -83,7 +84,7 @@ subroutine msk144sync(cdat,n,ntol,ndf,navmask,npeaks,fest,npklocs,nsuccess,c)
endif endif
enddo enddo
fest=1500+bestf fest=fc+bestf
c=cs c=cs
xcc=xccs xcc=xccs

View File

@ -78,6 +78,8 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
pnoise=-1.0 pnoise=-1.0
endif endif
fc=1500.0 !!! This will eventually come from the Rx Freq GUI box.
!!! Dupe checking should probaby be moved to mainwindow.cpp !!! Dupe checking should probaby be moved to mainwindow.cpp
if( nutc00 .ne. nutc0 ) then ! reset dupe checker if( nutc00 .ne. nutc0 ) then ! reset dupe checker
msglast=' ' msglast=' '
@ -109,8 +111,10 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
enddo enddo
pavg=sum(pow)/7.0 pavg=sum(pow)/7.0
np=7*NSPM np=8*NSPM
call msk144spd(cdat,np,ntol,nsuccess,msgreceived,fest,snr,tdec)
call msk144spd(cdat,np,ntol,nsuccess,msgreceived,fc,fest,tdec)
if( nsuccess .eq. 1 ) then if( nsuccess .eq. 1 ) then
tdec=tsec+tdec tdec=tsec+tdec
decsym=' & ' decsym=' & '
@ -120,10 +124,9 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
do iavg=1,NPATTERNS do iavg=1,NPATTERNS
iavmask=iavpatterns(1:8,iavg) iavmask=iavpatterns(1:8,iavg)
navg=sum(iavmask) navg=sum(iavmask)
! ndf=nint(7.0/navg) + 1
ndf=nint(7.0/navg) ndf=nint(7.0/navg)
npeaks=2 npeaks=2
call msk144sync(cdat(1:7*NSPM),7*864,ntol,ndf,iavmask,npeaks,fest,npkloc,nsyncsuccess,c) call msk144sync(cdat(1:8*NSPM),8,ntol,ndf,iavmask,npeaks,fc,fest,npkloc,nsyncsuccess,c)
if( nsyncsuccess .eq. 0 ) cycle if( nsyncsuccess .eq. 0 ) cycle
do ipk=1,npeaks do ipk=1,npeaks
@ -146,7 +149,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
msgreceived=' ' msgreceived=' '
! no decode - update noise level estimate used for calculating displayed snr. ! no decode - update noise level used for calculating displayed snr.
if( pnoise .lt. 0 ) then ! initialize noise level if( pnoise .lt. 0 ) then ! initialize noise level
pnoise=pavg pnoise=pavg
elseif( pavg .gt. pnoise ) then ! noise level is slow to rise elseif( pavg .gt. pnoise ) then ! noise level is slow to rise
@ -154,11 +157,12 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
elseif( pavg .lt. pnoise ) then ! and quick to fall elseif( pavg .lt. pnoise ) then ! and quick to fall
pnoise=pavg pnoise=pavg
endif endif
return return
999 continue 999 continue
! successful decode - estimate snr ! successful decode - estimate snr !!! noise estimate needs work
if( pnoise .gt. 0.0 ) then if( pnoise .gt. 0.0 ) then
snr0=10.0*log10(pmax/pnoise-1.0) snr0=10.0*log10(pmax/pnoise-1.0)
else else
@ -177,3 +181,4 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
1020 format(i6.6,i4,f5.1,i5,a3,a22,a1) 1020 format(i6.6,i4,f5.1,i5,a3,a22,a1)
return return
end subroutine mskrtd end subroutine mskrtd

View File

@ -5,6 +5,7 @@ subroutine tweak1(ca,jz,f0,cb)
complex ca(jz),cb(jz) complex ca(jz),cb(jz)
real*8 twopi real*8 twopi
complex*16 w,wstep complex*16 w,wstep
complex w4
data twopi/0.d0/ data twopi/0.d0/
save twopi save twopi

View File

@ -2964,7 +2964,7 @@ void MainWindow::guiUpdate()
//Once per second: //Once per second:
if(nsec != m_sec0) { if(nsec != m_sec0) {
qDebug() << m_config.contestMode() << m_config.realTimeDecode(); // qDebug() << m_config.contestMode() << m_config.realTimeDecode();
g_single_decode=m_config.single_decode(); g_single_decode=m_config.single_decode();
if(m_auto and m_mode=="Echo" and m_bEchoTxOK) { if(m_auto and m_mode=="Echo" and m_bEchoTxOK) {
progressBar.setMaximum(6); progressBar.setMaximum(6);