More work on real-time decoder for msk144.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@7107 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
Steven Franke 2016-09-22 19:42:05 +00:00
parent dd6cb2350a
commit 9831fb9cfc
4 changed files with 81 additions and 36 deletions

View File

@ -6,8 +6,8 @@ subroutine makepings(pings,npts,width,sig)
iping0=-999 iping0=-999
dt=1.0/12000.0 dt=1.0/12000.0
do i=1,14 do i=1,14,2
t0(i)=i !Make pings at t=1, 2, ... 14 s. t0(i)=i !Make pings at t=1, 3, ... 13 s.
enddo enddo
w=width w=width
amp=sig amp=sig

View File

@ -274,7 +274,7 @@ subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fret,snrret,tret)
! place the beginning of frame at index NSPM+1 ! place the beginning of frame at index NSPM+1
cdat2=cshift(cdat2,ic-(NSPM+1)) cdat2=cshift(cdat2,ic-(NSPM+1))
do iav=1,7 ! Hopefully we can eliminate some of these after looking at more examples do iav=1,8 ! Hopefully we can eliminate some of these after looking at more examples
if( iav .eq. 1 ) then if( iav .eq. 1 ) then
c=cdat2(NSPM+1:2*NSPM) c=cdat2(NSPM+1:2*NSPM)
elseif( iav .eq. 2 ) then elseif( iav .eq. 2 ) then

View File

@ -1,4 +1,4 @@
subroutine msk144sync(cdat,n,ntol,ndf,iavmask,npeaks,fest,snr,ipklocs,pkamps,c) subroutine msk144sync(cdat,n,ntol,ndf,navmask,npeaks,fest,npklocs,nsuccess,c)
parameter (NSPM=864) parameter (NSPM=864)
complex cdat(n) complex cdat(n)
@ -11,8 +11,8 @@ subroutine msk144sync(cdat,n,ntol,ndf,iavmask,npeaks,fest,snr,ipklocs,pkamps,c)
integer s8(8) integer s8(8)
integer iloc(1) integer iloc(1)
integer ipklocs(npeaks) integer npklocs(npeaks)
integer iavmask(8) ! defines which frames to average integer navmask(8) ! defines which frames to average
real cbi(42),cbq(42) real cbi(42),cbq(42)
real pkamps(npeaks) real pkamps(npeaks)
@ -51,7 +51,7 @@ subroutine msk144sync(cdat,n,ntol,ndf,iavmask,npeaks,fest,snr,ipklocs,pkamps,c)
first=.false. first=.false.
endif endif
navg=sum(iavmask) navg=sum(navmask)
xmax=0.0 xmax=0.0
bestf=0.0 bestf=0.0
do ifr=-ntol,ntol,ndf !Find freq that maximizes sync do ifr=-ntol,ntol,ndf !Find freq that maximizes sync
@ -61,7 +61,7 @@ subroutine msk144sync(cdat,n,ntol,ndf,iavmask,npeaks,fest,snr,ipklocs,pkamps,c)
do i=1,8 do i=1,8
ib=(i-1)*NSPM+1 ib=(i-1)*NSPM+1
ie=ib+NSPM-1 ie=ib+NSPM-1
if( iavmask(i) .eq. 1 ) then if( navmask(i) .eq. 1 ) then
c(1:NSPM)=c(1:NSPM)+cdat2(ib:ie) c(1:NSPM)=c(1:NSPM)+cdat2(ib:ie)
endif endif
enddo enddo
@ -91,12 +91,16 @@ subroutine msk144sync(cdat,n,ntol,ndf,iavmask,npeaks,fest,snr,ipklocs,pkamps,c)
do ipk=1,npeaks do ipk=1,npeaks
iloc=maxloc(xcc) iloc=maxloc(xcc)
ic2=iloc(1) ic2=iloc(1)
ipklocs(ipk)=ic2 npklocs(ipk)=ic2
pkamps(ipk)=xcc(ic2-1) pkamps(ipk)=xcc(ic2-1)
xcc(max(0,ic2-7):min(NSPM-1,ic2+7))=0.0 xcc(max(0,ic2-7):min(NSPM-1,ic2+7))=0.0
enddo enddo
!write(*,*) xmax,bestf,fest,pkamps(1)/(48.0*sqrt(float(navg))),ipklocs(1),ipklocs(2) if( xmax .lt. 0.7 ) then
snr=-6.0 nsuccess=0
else
nsuccess=1
endif
return return
end subroutine msk144sync end subroutine msk144sync

View File

@ -9,9 +9,11 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
parameter (NFFT1=8192) !FFT size for making analytic signal parameter (NFFT1=8192) !FFT size for making analytic signal
parameter (NAVGMAX=7) !Coherently average up to 7 frames parameter (NAVGMAX=7) !Coherently average up to 7 frames
parameter (NPTSMAX=7*NSPM) !Max points analyzed at once parameter (NPTSMAX=7*NSPM) !Max points analyzed at once
parameter (NPATTERNS=4) !Number of frame averaging patterns to try
character*3 decsym !"&" for mskspd or "^" for long averages character*3 decsym !"&" for mskspd or "^" for long averages
character*22 msgreceived !Decoded message character*22 msgreceived !Decoded message
character*22 msglast !!! temporary - used for dupechecking
character*80 line !Formatted line with UTC dB T Freq Msg character*80 line !Formatted line with UTC dB T Freq Msg
complex cdat(NFFT1) !Analytic signal complex cdat(NFFT1) !Analytic signal
@ -22,30 +24,28 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
! integer*8 count0,count1,count2,count3,clkfreq ! integer*8 count0,count1,count2,count3,clkfreq
integer*2 id2(NZ) !Raw 16-bit data integer*2 id2(NZ) !Raw 16-bit data
integer iavmask(8) integer iavmask(8)
integer iavpatterns(8,6) integer iavpatterns(8,NPATTERNS)
integer s8(8) integer s8(8)
integer ipeaks(10) integer npkloc(10)
integer nav(6) integer nav(6)
real cbi(42),cbq(42) real cbi(42),cbq(42)
real d(NFFT1) real d(NFFT1)
real pkamps(10)
real pp(12) !Half-sine pulse shape real pp(12) !Half-sine pulse shape
real xmc(6) real pow(7)
real xmc(NPATTERNS)
logical first logical first
data first/.true./ data first/.true./
data s8/0,1,1,1,0,0,1,0/ data s8/0,1,1,1,0,0,1,0/
data nav/1,2,3,5,7,9/ data nav/1,2,3,5,7,9/
data iavpatterns/ & data iavpatterns/ &
1,1,1,0,0,0,0,0, & 1,1,1,1,0,0,0,0, &
0,1,1,1,0,0,0,0, & 0,0,1,1,1,1,0,0, &
0,0,1,1,1,0,0,0, &
1,1,1,1,1,0,0,0, & 1,1,1,1,1,0,0,0, &
0,0,1,1,1,1,1,0, &
1,1,1,1,1,1,1,0/ 1,1,1,1,1,1,1,0/
data xmc/1.5,2.5,3.5,2.5,4.5,3.5/ !Used to label decode with time at center of averaging mask data xmc/2.0,4.5,2.5,3.5/ !Used to label decode with time at center of averaging mask
save first,cb,fs,pi,twopi,dt,s8,pp,t03,t12,nutc00 save first,cb,fs,pi,twopi,dt,s8,pp,t03,t12,nutc00,pnoise,nsnrlast,msglast
! call system_clock(count0,clkfreq) ! call system_clock(count0,clkfreq)
if(first) then if(first) then
@ -74,9 +74,19 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
first=.false. first=.false.
t03=0.0 t03=0.0
t12=0.0 t12=0.0
nutc00=-1 nutc00=nutc0
pnoise=-1.0
endif endif
!!! Dupe checking should probaby be moved to mainwindow.cpp
if( nutc00 .ne. nutc0 ) then ! reset dupe checker
msglast=' '
nsnrlast=-99
nutc00=nutc0
endif
tframe=float(NSPM)/12000.0
line=char(0)
msgreceived=' ' msgreceived=' '
max_iterations=10 max_iterations=10
niterations=0 niterations=0
@ -88,6 +98,17 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
d(NZ+1:NFFT1)=0. d(NZ+1:NFFT1)=0.
call analytic(d,NZ,NFFT1,cdat) !Convert to analytic signal and filter call analytic(d,NZ,NFFT1,cdat) !Convert to analytic signal and filter
pmax=-99
do i=1,7
ib=(i-1)*NSPM+1
ie=ib+NSPM-1
pow(i)=dot_product(cdat(ib:ie),cdat(ib:ie))*rms**2
if( pow(i) .gt. pmax ) then
pmax=pow(i)
endif
enddo
pavg=sum(pow)/7.0
np=7*NSPM np=7*NSPM
call msk144spd(cdat,np,ntol,nsuccess,msgreceived,fest,snr,tdec) call msk144spd(cdat,np,ntol,nsuccess,msgreceived,fest,snr,tdec)
if( nsuccess .eq. 1 ) then if( nsuccess .eq. 1 ) then
@ -96,30 +117,25 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
goto 999 goto 999
endif endif
tframe=float(NSPM)/12000.0 do iavg=1,NPATTERNS
nmessages=0
line=char(0)
npts=7168
do iavg=1,6
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) + 1
ndf=nint(7.0/navg) ndf=nint(7.0/navg)
npeaks=2 npeaks=2
call msk144sync(cdat(1:8*NSPM),8*864,ntol,ndf,iavmask,npeaks,fest,snr,ipeaks,pkamps,c) call msk144sync(cdat(1:7*NSPM),7*864,ntol,ndf,iavmask,npeaks,fest,npkloc,nsyncsuccess,c)
if( nsyncsuccess .eq. 0 ) cycle
do ipk=1,2 do ipk=1,npeaks
do is=1,3 do is=1,3
ic0=ipeaks(ipk) ic0=npkloc(ipk)
if(is.eq.2) ic0=max(1,ic0-1) if(is.eq.2) ic0=max(1,ic0-1)
if(is.eq.3) ic0=min(NSPM,ic0+1) if(is.eq.3) ic0=min(NSPM,ic0+1)
ct=cshift(c,ic0-1) ct=cshift(c,ic0-1)
call msk144decodeframe(ct,msgreceived,nsuccess) call msk144decodeframe(ct,msgreceived,ndecodesuccess)
if(nsuccess .gt. 0) then if(ndecodesuccess .gt. 0) then
tdec=tsec+xmc(iavg)*tframe tdec=tsec+xmc(iavg)*tframe
decsym=' ^ ' decsym=' ^ '
goto 999 goto 999
@ -129,9 +145,34 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,line)
enddo enddo
msgreceived=' ' msgreceived=' '
! no decode - update noise level estimate used for calculating displayed snr.
if( pnoise .lt. 0 ) then ! initialize noise level
pnoise=pavg
elseif( pavg .gt. pnoise ) then ! noise level is slow to rise
pnoise=0.9*pnoise+0.1*pavg
elseif( pavg .lt. pnoise ) then ! and quick to fall
pnoise=pavg
endif
return return
999 continue 999 continue
nsnr=nint(snr)
! successful decode - estimate snr
if( pnoise .gt. 0.0 ) then
snr0=10.0*log10(pmax/pnoise-1.0)
else
snr0=0.0
endif
nsnr=nint(snr0)
!!!! Temporary - dupe check. Only print if new message, or higher snr.
if( msgreceived .eq. msglast .and. nsnr .le. nsnrlast ) return
msglast=msgreceived
nsnrlast=nsnr
if( nsnr .lt. -8 ) nsnr=-8
if( nsnr .gt. 24 ) nsnr=24
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived,char(0) write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived,char(0)
1020 format(i6.6,i4,f5.1,i5,a3,a22,a1) 1020 format(i6.6,i4,f5.1,i5,a3,a22,a1)
return return