mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2025-02-03 09:44:24 -05:00
More progress on SWL mode.
git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@7449 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
parent
6d3ca346e0
commit
c47403642e
@ -135,30 +135,32 @@ subroutine msk40decodeframe(c,mycall,hiscall,xsnr,bswl,nhasharray, &
|
|||||||
nrxhash=(imsg-nrxrpt)/16
|
nrxhash=(imsg-nrxrpt)/16
|
||||||
|
|
||||||
if(nhammd.le.4 .and. cord .lt. 0.65 .and. nrxhash.eq.ihash) then
|
if(nhammd.le.4 .and. cord .lt. 0.65 .and. nrxhash.eq.ihash) then
|
||||||
!write(*,*) 'decodeframe 1',nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma
|
!write(*,*) 'decodeframe 1',nbadsync,nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma
|
||||||
nsuccess=1
|
nsuccess=1
|
||||||
write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(mycall), &
|
write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(mycall), &
|
||||||
trim(hiscall),">",rpt(nrxrpt)
|
trim(hiscall),">",rpt(nrxrpt)
|
||||||
return
|
return
|
||||||
elseif(bswl .and. nhammd.le.2 .and. cord.lt.0.40 .and. xsnr .gt. -3.0) then
|
! elseif(bswl .and. nhammd.le.2 .and. cord.lt.0.40 .and. xsnr .gt. -3.0) then
|
||||||
|
elseif(bswl .and. nhammd.le.4 .and. cord.lt.0.65 ) then
|
||||||
do i=1,nrecent
|
do i=1,nrecent
|
||||||
do j=i+1,nrecent
|
do j=i+1,nrecent
|
||||||
if( nrxhash .eq. nhasharray(i,j) ) then
|
if( nrxhash .eq. nhasharray(i,j) ) then
|
||||||
nsuccess=2
|
nsuccess=2
|
||||||
write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(recent_calls(i)), &
|
write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(recent_calls(i)), &
|
||||||
trim(recent_calls(j)),">",rpt(nrxrpt)
|
trim(recent_calls(j)),">",rpt(nrxrpt)
|
||||||
!write(*,*) 'decodeframe 2',nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma
|
!write(*,*) 'decodeframe 2',nbadsync,nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma
|
||||||
elseif( nrxhash .eq. nhasharray(j,i) ) then
|
elseif( nrxhash .eq. nhasharray(j,i) ) then
|
||||||
nsuccess=2
|
nsuccess=2
|
||||||
write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(recent_calls(j)), &
|
write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(recent_calls(j)), &
|
||||||
trim(recent_calls(i)),">",rpt(nrxrpt)
|
trim(recent_calls(i)),">",rpt(nrxrpt)
|
||||||
!write(*,*) 'decodeframe 3',nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma
|
!write(*,*) 'decodeframe 3',nbadsync,nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma
|
||||||
endif
|
endif
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
if(nsuccess.eq.0 .and. nhammd.le.2 .and. cord.lt.0.40 .and. xsnr.gt.0.0 ) then
|
! if(nsuccess.eq.0 .and. nhammd.le.2 .and. cord.lt.0.40 .and. xsnr.gt. -3.0 ) then
|
||||||
!write(*,*) 'decodeframe 4',bswl,nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma
|
if(nsuccess.eq.0) then
|
||||||
nsuccess=3
|
nsuccess=3
|
||||||
|
!write(*,*) 'decodeframe 4',bswl,nbadsync,nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma,nsuccess
|
||||||
write(msgreceived,'(a1,i4.4,a1,1x,a4)') "<",nrxhash,">",rpt(nrxrpt)
|
write(msgreceived,'(a1,i4.4,a1,1x,a4)') "<",nrxhash,">",rpt(nrxrpt)
|
||||||
endif
|
endif
|
||||||
endif
|
endif
|
||||||
|
114
lib/mskrtd.f90
114
lib/mskrtd.f90
@ -10,14 +10,16 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
parameter (NFFT1=8192) !FFT size for making analytic signal
|
parameter (NFFT1=8192) !FFT size for making analytic signal
|
||||||
parameter (NPATTERNS=4) !Number of frame averaging patterns to try
|
parameter (NPATTERNS=4) !Number of frame averaging patterns to try
|
||||||
parameter (NRECENT=10) !Number of recent calls to remember
|
parameter (NRECENT=10) !Number of recent calls to remember
|
||||||
|
parameter (NSHMEM=250) !Number of recent SWL messages to remember
|
||||||
|
|
||||||
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*22 msglast,msglastswl !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
|
||||||
character*12 mycall,hiscall
|
character*12 mycall,hiscall
|
||||||
character*6 mygrid
|
character*6 mygrid
|
||||||
character*12 recent_calls(NRECENT)
|
character*12 recent_calls(NRECENT)
|
||||||
|
character*22 recent_shmsgs(NSHMEM)
|
||||||
|
|
||||||
complex cdat(NFFT1) !Analytic signal
|
complex cdat(NFFT1) !Analytic signal
|
||||||
complex c(NSPM) !Coherently averaged complex data
|
complex c(NSPM) !Coherently averaged complex data
|
||||||
@ -28,6 +30,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
integer iavpatterns(8,NPATTERNS)
|
integer iavpatterns(8,NPATTERNS)
|
||||||
integer npkloc(10)
|
integer npkloc(10)
|
||||||
integer nhasharray(NRECENT,NRECENT)
|
integer nhasharray(NRECENT,NRECENT)
|
||||||
|
integer nsnrlast,nsnrlastswl
|
||||||
|
|
||||||
real d(NFFT1)
|
real d(NFFT1)
|
||||||
real pow(8)
|
real pow(8)
|
||||||
@ -39,7 +42,8 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
logical*1 first
|
logical*1 first
|
||||||
logical*1 trained
|
logical*1 trained
|
||||||
logical*1 bshdecode
|
logical*1 bshdecode
|
||||||
logical*1 noprint
|
logical*1 seenb4
|
||||||
|
logical*1 bflag
|
||||||
|
|
||||||
data first/.true./
|
data first/.true./
|
||||||
data iavpatterns/ &
|
data iavpatterns/ &
|
||||||
@ -48,8 +52,8 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
1,1,1,1,1,0,0,0, &
|
1,1,1,1,1,0,0,0, &
|
||||||
1,1,1,1,1,1,1,0/
|
1,1,1,1,1,1,1,0/
|
||||||
data xmc/2.0,4.5,2.5,3.5/ !Used to set time at center of averaging mask
|
data xmc/2.0,4.5,2.5,3.5/ !Used to set time at center of averaging mask
|
||||||
save first,tsec0,nutc00,pnoise,nsnrlast,msglast,cdat,pcoeffs,trained, &
|
save first,tsec0,nutc00,pnoise,cdat,pcoeffs,trained,msglast,msglastswl, &
|
||||||
recent_calls,nhasharray
|
nsnrlast,nsnrlastswl,recent_calls,nhasharray,recent_shmsgs
|
||||||
|
|
||||||
if(first) then
|
if(first) then
|
||||||
tsec0=tsec
|
tsec0=tsec
|
||||||
@ -59,7 +63,14 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
do i=1,nrecent
|
do i=1,nrecent
|
||||||
recent_calls(i)(1:12)=' '
|
recent_calls(i)(1:12)=' '
|
||||||
enddo
|
enddo
|
||||||
|
do i=1,nshmem
|
||||||
|
recent_shmsgs(i)(1:22)=' '
|
||||||
|
enddo
|
||||||
trained=.false.
|
trained=.false.
|
||||||
|
msglast=' '
|
||||||
|
msglastswl=' '
|
||||||
|
nsnrlast=-99
|
||||||
|
nsnrlastswl=-99
|
||||||
first=.false.
|
first=.false.
|
||||||
endif
|
endif
|
||||||
|
|
||||||
@ -68,7 +79,9 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
! Dupe checking setup
|
! Dupe checking setup
|
||||||
if(nutc00.ne.nutc0 .or. tsec.lt.tsec0) then ! reset dupe checker
|
if(nutc00.ne.nutc0 .or. tsec.lt.tsec0) then ! reset dupe checker
|
||||||
msglast=' '
|
msglast=' '
|
||||||
|
msglastswl=' '
|
||||||
nsnrlast=-99
|
nsnrlast=-99
|
||||||
|
nsnrlastswl=-99
|
||||||
nutc00=nutc0
|
nutc00=nutc0
|
||||||
endif
|
endif
|
||||||
|
|
||||||
@ -83,7 +96,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
fac=1.0/rms
|
fac=1.0/rms
|
||||||
d(1:NZ)=fac*d(1:NZ)
|
d(1:NZ)=fac*d(1:NZ)
|
||||||
d(NZ+1:NFFT1)=0.
|
d(NZ+1:NFFT1)=0.
|
||||||
call analytic(d,NZ,NFFT1,cdat,pcoeffs,brxequal,.true.) !Convert to analytic signal and filter
|
call analytic(d,NZ,NFFT1,cdat,pcoeffs,brxequal,.true.)
|
||||||
|
|
||||||
! Calculate average power for each frame and for the entire block.
|
! Calculate average power for each frame and for the entire block.
|
||||||
! If decode is successful, largest power will be taken as signal+noise.
|
! If decode is successful, largest power will be taken as signal+noise.
|
||||||
@ -101,13 +114,13 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
! center a 3-frame analysis window and attempts to decode each of the
|
! center a 3-frame analysis window and attempts to decode each of the
|
||||||
! 3 frames along with 2- and 3-frame averages.
|
! 3 frames along with 2- and 3-frame averages.
|
||||||
np=8*NSPM
|
np=8*NSPM
|
||||||
call msk144spd(cdat,np,ntol,nsuccess,msgreceived,fc,fest,tdec,navg,ct, &
|
call msk144spd(cdat,np,ntol,ndecodesuccess,msgreceived,fc,fest,tdec,navg,ct, &
|
||||||
softbits,recent_calls,nrecent)
|
softbits,recent_calls,nrecent)
|
||||||
if(nsuccess.eq.0 .and. bshmsg) then
|
if(ndecodesuccess.eq.0 .and. bshmsg) then
|
||||||
call msk40spd(cdat,np,ntol,mycall(1:6),hiscall(1:6),bswl,nhasharray, &
|
call msk40spd(cdat,np,ntol,mycall(1:6),hiscall(1:6),bswl,nhasharray, &
|
||||||
recent_calls,nrecent,nsuccess,msgreceived,fc,fest,tdec,navg)
|
recent_calls,nrecent,ndecodesuccess,msgreceived,fc,fest,tdec,navg)
|
||||||
endif
|
endif
|
||||||
if( nsuccess .ge. 1 ) then
|
if( ndecodesuccess .ge. 1 ) then
|
||||||
tdec=tsec+tdec
|
tdec=tsec+tdec
|
||||||
ipk=0
|
ipk=0
|
||||||
is=0
|
is=0
|
||||||
@ -126,7 +139,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
navg=sum(iavmask)
|
navg=sum(iavmask)
|
||||||
deltaf=10.0/real(navg) ! search increment for frequency sync
|
deltaf=10.0/real(navg) ! search increment for frequency sync
|
||||||
npeaks=2
|
npeaks=2
|
||||||
call msk144sync(cdat(1:8*NSPM),8,ntol,deltaf,iavmask,npeaks,fc, &
|
call msk144sync(cdat(1:8*NSPM),8,ntol,deltaf,iavmask,npeaks,fc, &
|
||||||
fest,npkloc,nsyncsuccess,xmax,c)
|
fest,npkloc,nsyncsuccess,xmax,c)
|
||||||
if( nsyncsuccess .eq. 0 ) cycle
|
if( nsyncsuccess .eq. 0 ) cycle
|
||||||
|
|
||||||
@ -173,34 +186,51 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
|
|
||||||
if(.not. bshdecode) then
|
if(.not. bshdecode) then
|
||||||
call msk144signalquality(ct,snr0,fest,tdec,softbits,msgreceived,hiscall, &
|
call msk144signalquality(ct,snr0,fest,tdec,softbits,msgreceived,hiscall, &
|
||||||
ncorrected,eyeopening,trained,pcoeffs)
|
ncorrected,eyeopening,trained,pcoeffs)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
! Dupe check. Only print if new message, or higher snr.
|
decsym=' & '
|
||||||
if(msgreceived.ne.msglast .or. nsnr.gt.nsnrlast .or. tsec.lt.tsec0) then
|
if( brxequal .and. (.not. trained) ) decsym=' ^ '
|
||||||
call update_hasharray(recent_calls,nrecent,nhasharray)
|
if( brxequal .and. trained ) decsym=' $ '
|
||||||
|
if( (.not. brxequal) .and. trained ) decsym=' @ '
|
||||||
|
if( msgreceived(1:1).eq.'<') then
|
||||||
|
ncorrected=0
|
||||||
|
eyeopening=0.0
|
||||||
|
endif
|
||||||
|
|
||||||
|
if( nsnr .lt. -8 ) nsnr=-8
|
||||||
|
if( nsnr .gt. 24 ) nsnr=24
|
||||||
|
|
||||||
|
! Dupe check.
|
||||||
|
bflag=ndecodesuccess.eq.1 .and. &
|
||||||
|
(msgreceived.ne.msglast .or. nsnr.gt.nsnrlast .or. tsec.lt.tsec0)
|
||||||
|
if(bflag) then
|
||||||
msglast=msgreceived
|
msglast=msgreceived
|
||||||
nsnrlast=nsnr
|
nsnrlast=nsnr
|
||||||
if( nsnr .lt. -8 ) nsnr=-8
|
|
||||||
if( nsnr .gt. 24 ) nsnr=24
|
|
||||||
if(.not. bshdecode) then
|
if(.not. bshdecode) then
|
||||||
|
call update_hasharray(recent_calls,nrecent,nhasharray)
|
||||||
call fix_contest_msg(mycall(1:6),mygrid,hiscall(1:6),msgreceived)
|
call fix_contest_msg(mycall(1:6),mygrid,hiscall(1:6),msgreceived)
|
||||||
endif
|
endif
|
||||||
decsym=' & '
|
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived, &
|
||||||
if( brxequal .and. (.not. trained) ) decsym=' ^ '
|
navg,ncorrected,eyeopening,char(0)
|
||||||
if( brxequal .and. trained ) decsym=' $ '
|
1020 format(i6.6,i4,f5.1,i5,a3,a22,i2,i3,f5.1,a1)
|
||||||
if( (.not. brxequal) .and. trained ) decsym=' @ '
|
elseif(bswl .and. ndecodesuccess.ge.2) then
|
||||||
if( msgreceived(1:1).eq.'<') then
|
seenb4=.false.
|
||||||
ncorrected=0
|
do i=1,nshmem
|
||||||
eyeopening=0.0
|
if( msgreceived .eq. recent_shmsgs(i) ) then
|
||||||
endif
|
seenb4=.true.
|
||||||
noprint = bswl .and. &
|
endif
|
||||||
((nsuccess.eq.2 .and. nsnr.lt.-3).or.(nsuccess.eq.3 .and. nsnr.lt.-3))
|
enddo
|
||||||
if( .not.noprint ) then
|
call update_recent_shmsgs(msgreceived,recent_shmsgs,nshmem)
|
||||||
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived, &
|
bflag=seenb4 .and. &
|
||||||
navg,ncorrected,eyeopening,char(0)
|
(msgreceived.ne.msglastswl .or. nsnr.gt.nsnrlastswl .or. tsec.lt.tsec0) &
|
||||||
1020 format(i6.6,i4,f5.1,i5,a3,a22,i2,i3,f5.1,a1)
|
.and. nsnr.gt.-6
|
||||||
endif
|
if(bflag) then
|
||||||
|
msglastswl=msgreceived
|
||||||
|
nsnrlastswl=nsnr
|
||||||
|
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived, &
|
||||||
|
navg,ncorrected,eyeopening,char(0)
|
||||||
|
endif
|
||||||
endif
|
endif
|
||||||
999 tsec0=tsec
|
999 tsec0=tsec
|
||||||
|
|
||||||
@ -208,3 +238,23 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
|
|||||||
end subroutine mskrtd
|
end subroutine mskrtd
|
||||||
|
|
||||||
include 'fix_contest_msg.f90'
|
include 'fix_contest_msg.f90'
|
||||||
|
|
||||||
|
subroutine update_recent_shmsgs(message,msgs,nsize)
|
||||||
|
character*22 msgs(nsize)
|
||||||
|
character*22 message
|
||||||
|
logical*1 seen
|
||||||
|
|
||||||
|
seen=.false.
|
||||||
|
do i=1,nsize
|
||||||
|
if( msgs(i) .eq. message ) seen=.true.
|
||||||
|
enddo
|
||||||
|
|
||||||
|
if( .not. seen ) then
|
||||||
|
do i=nsize,2,-1
|
||||||
|
msgs(i)=msgs(i-1)
|
||||||
|
enddo
|
||||||
|
msgs(1)=message
|
||||||
|
endif
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine update_recent_shmsgs
|
||||||
|
Loading…
Reference in New Issue
Block a user