Merge branch 'hotfix-wsjtx-2.0.0-rc2' of bitbucket.org:k1jt/wsjtx into hotfix-wsjtx-2.0.0-rc2

This commit is contained in:
Joe Taylor 2018-09-24 16:31:20 -04:00
commit 4414280471
7 changed files with 79 additions and 56 deletions

View File

@ -1,10 +1,11 @@
module packjt77 module packjt77
! These variables are accessible from outside via "use packjt": ! These variables are accessible from outside via "use packjt77":
parameter (MAXHASH=1000) parameter (MAXHASH=1000,MAXRECENT=10)
character*13 callsign(MAXHASH) character*13 callsign(MAXHASH)
integer ihash10(MAXHASH),ihash12(MAXHASH),ihash22(MAXHASH) integer ihash10(MAXHASH),ihash12(MAXHASH),ihash22(MAXHASH)
integer n28a,n28b,nzhash integer n28a,n28b,nzhash
character*13 recent_calls(MAXRECENT)
contains contains
@ -358,11 +359,13 @@ subroutine unpack77(c77,msg,unpk77_success)
i=index(call_1,' ') i=index(call_1,' ')
if(i.ge.4 .and. ipa.eq.1 .and. i3.eq.1) call_1(i:i+1)='/R' if(i.ge.4 .and. ipa.eq.1 .and. i3.eq.1) call_1(i:i+1)='/R'
if(i.ge.4 .and. ipa.eq.1 .and. i3.eq.2) call_1(i:i+1)='/P' if(i.ge.4 .and. ipa.eq.1 .and. i3.eq.2) call_1(i:i+1)='/P'
if(i.ge.4) call add_call_to_recent_calls(call_1)
endif endif
if(index(call_2,'<').le.0) then if(index(call_2,'<').le.0) then
i=index(call_2,' ') i=index(call_2,' ')
if(i.ge.4 .and. ipb.eq.1 .and. i3.eq.1) call_2(i:i+1)='/R' if(i.ge.4 .and. ipb.eq.1 .and. i3.eq.1) call_2(i:i+1)='/R'
if(i.ge.4 .and. ipb.eq.1 .and. i3.eq.2) call_2(i:i+1)='/P' if(i.ge.4 .and. ipb.eq.1 .and. i3.eq.2) call_2(i:i+1)='/P'
if(i.ge.4) call add_call_to_recent_calls(call_2)
endif endif
if(igrid4.le.MAXGRID4) then if(igrid4.le.MAXGRID4) then
n=igrid4 n=igrid4
@ -1153,6 +1156,7 @@ subroutine unpacktext77(c71,c13)
return return
end subroutine unpacktext77 end subroutine unpacktext77
<<<<<<< HEAD
subroutine mp_short_ops(w,u) subroutine mp_short_ops(w,u)
character*1 w(*),u(*) character*1 w(*),u(*)
integer i,ireg,j,n,ir,iv,ii1,ii2 integer i,ireg,j,n,ir,iv,ii1,ii2
@ -1197,5 +1201,26 @@ subroutine mp_short_ops(w,u)
return return
end subroutine mp_short_ops end subroutine mp_short_ops
=======
subroutine add_call_to_recent_calls(callsign)
character*13 callsign
logical ladd
! only add if the callsign is not already on the list
ladd=.true.
do i=1,MAXRECENT-1 ! if callsign is at the end of the list add it again
if(recent_calls(i).eq.callsign) ladd=.false.
enddo
if(ladd) then
do i=MAXRECENT,2,-1
recent_calls(i)=recent_calls(i-1)
enddo
recent_calls(1)=callsign
endif
return
end subroutine add_call_to_recent_calls
>>>>>>> d66724f6e9dd8fd8f1340aec9e5c0ebf45a681ac
end module packjt77 end module packjt77

View File

@ -1,9 +1,8 @@
subroutine msk144decodeframe(c,softbits,msgreceived,nsuccess,recent_calls,nrecent) subroutine msk144decodeframe(c,softbits,msgreceived,nsuccess)
! use timer_module, only: timer ! use timer_module, only: timer
use packjt77 use packjt77
parameter (NSPM=864) parameter (NSPM=864)
character*37 msgreceived character*37 msgreceived
character*12 recent_calls(nrecent)
character*77 c77 character*77 c77
complex cb(42) complex cb(42)
complex cfac,cca,ccb complex cfac,cca,ccb

View File

@ -1,13 +1,13 @@
subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fc,fret,tret,navg,ct, & subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fc,fret,tret,navg,ct, &
softbits,recent_calls,nrecent) softbits)
! MSK144 short-ping-decoder ! MSK144 short-ping-decoder
use packjt77
use timer_module, only: timer use timer_module, only: timer
parameter (NSPM=864, MAXSTEPS=100, NFFT=NSPM, MAXCAND=5, NPATTERNS=6) parameter (NSPM=864, MAXSTEPS=100, NFFT=NSPM, MAXCAND=5, NPATTERNS=6)
character*37 msgreceived character*37 msgreceived
character*12 recent_calls(nrecent)
complex cbig(n) complex cbig(n)
complex cdat(3*NSPM) !Analytic signal complex cdat(3*NSPM) !Analytic signal
complex c(NSPM) complex c(NSPM)
@ -179,8 +179,7 @@ subroutine msk144spd(cbig,n,ntol,nsuccess,msgreceived,fc,fret,tret,navg,ct, &
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,softbits,msgreceived,ndecodesuccess, & call msk144decodeframe(ct,softbits,msgreceived,ndecodesuccess)
recent_calls,nrecent)
if( ndecodesuccess .gt. 0 ) then if( ndecodesuccess .gt. 0 ) then
tret=(nstart(icand)+NSPM/2)/fs tret=(nstart(icand)+NSPM/2)/fs
fret=fest fret=fest

View File

@ -1,19 +1,19 @@
subroutine msk40decodeframe(c,mycall,hiscall,xsnr,bswl,nhasharray, & subroutine msk40decodeframe(c,mycall,hiscall,xsnr,bswl,nhasharray, &
recent_calls,nrecent,msgreceived,nsuccess) msgreceived,nsuccess)
! use timer_module, only: timer ! use timer_module, only: timer
use packjt77
parameter (NSPM=240) parameter (NSPM=240)
character*4 rpt(0:15) character*4 rpt(0:15)
character*6 mycall,hiscall,mycall0,hiscall0 character*6 mycall,hiscall,mycall0,hiscall0
character*22 hashmsg,msgreceived character*22 hashmsg,msgreceived
character*12 recent_calls(nrecent)
complex cb(42) complex cb(42)
complex cfac,cca complex cfac,cca
complex c(NSPM) complex c(NSPM)
integer*1 cw(32) integer*1 cw(32)
integer*1 decoded(16) integer*1 decoded(16)
integer s8r(8),hardbits(40) integer s8r(8),hardbits(40)
integer nhasharray(nrecent,nrecent) integer nhasharray(MAXRECENT,MAXRECENT)
real*8 dt, fs, pi, twopi real*8 dt, fs, pi, twopi
real cbi(42),cbq(42) real cbi(42),cbq(42)
real pp(12) real pp(12)
@ -115,7 +115,6 @@ subroutine msk40decodeframe(c,mycall,hiscall,xsnr,bswl,nhasharray, &
max_iterations=5 max_iterations=5
call bpdecode40(llr,max_iterations,decoded,niterations) call bpdecode40(llr,max_iterations,decoded,niterations)
if( niterations .ge. 0.0 ) then if( niterations .ge. 0.0 ) then
call encode_msk40(decoded,cw) call encode_msk40(decoded,cw)
nhammd=0 nhammd=0
@ -133,33 +132,28 @@ subroutine msk40decodeframe(c,mycall,hiscall,xsnr,bswl,nhasharray, &
enddo enddo
nrxrpt=iand(imsg,15) nrxrpt=iand(imsg,15)
nrxhash=(imsg-nrxrpt)/16 nrxhash=(imsg-nrxrpt)/16
if(nhammd.le.4 .and. cord .lt. 0.65 .and. & if(nhammd.le.4 .and. cord .lt. 0.65 .and. &
nrxhash.eq.ihash .and. nrxrpt.ge.7) then nrxhash.eq.ihash .and. nrxrpt.ge.7) then
!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.4 .and. cord.lt.0.65 .and. nrxrpt.ge.7 ) then elseif(bswl .and. nhammd.le.4 .and. cord.lt.0.65 .and. nrxrpt.ge.7 ) then
do i=1,nrecent do i=1,MAXRECENT
do j=i+1,nrecent do j=i+1,MAXRECENT
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',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',nbadsync,nhammd,cord,nrxhash,nrxrpt,ihash,xsnr,sigma
endif endif
enddo enddo
enddo enddo
if(nsuccess.eq.0) then 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

View File

@ -1,13 +1,13 @@
subroutine msk40spd(cbig,n,ntol,mycall,hiscall,bswl,nhasharray,recent_calls, & subroutine msk40spd(cbig,n,ntol,mycall,hiscall,bswl,nhasharray, &
nrecent,nsuccess,msgreceived,fc,fret,tret,navg) nsuccess,msgreceived,fc,fret,tret,navg)
! msk40 short-ping-decoder ! msk40 short-ping-decoder
use packjt77
use timer_module, only: timer use timer_module, only: timer
parameter (NSPM=240, MAXSTEPS=150, NFFT=NSPM, MAXCAND=5, NPATTERNS=6) parameter (NSPM=240, MAXSTEPS=150, NFFT=NSPM, MAXCAND=5, NPATTERNS=6)
character*6 mycall,hiscall character*6 mycall,hiscall
character*22 msgreceived character*22 msgreceived
character*12 recent_calls(nrecent)
complex cbig(n) complex cbig(n)
complex cdat(3*NSPM) !Analytic signal complex cdat(3*NSPM) !Analytic signal
complex c(NSPM) complex c(NSPM)
@ -19,7 +19,6 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,bswl,nhasharray,recent_calls, &
integer navpatterns(3,NPATTERNS) integer navpatterns(3,NPATTERNS)
integer navmask(3) integer navmask(3)
integer nstart(MAXCAND) integer nstart(MAXCAND)
integer nhasharray(nrecent,nrecent)
logical ismask(NFFT) logical ismask(NFFT)
logical*1 bswl logical*1 bswl
real detmet(-2:MAXSTEPS+3) real detmet(-2:MAXSTEPS+3)
@ -181,7 +180,7 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,bswl,nhasharray,recent_calls, &
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 msk40decodeframe(ct,mycall,hiscall,xsnr,bswl,nhasharray, & call msk40decodeframe(ct,mycall,hiscall,xsnr,bswl,nhasharray, &
recent_calls,nrecent,msgreceived,ndecodesuccess) msgreceived,ndecodesuccess)
if( ndecodesuccess .gt. 0 ) then if( ndecodesuccess .gt. 0 ) then
!write(*,*) icand, iav, ipk, is, tret, fret, msgreceived !write(*,*) icand, iav, ipk, is, tret, fret, msgreceived
tret=(nstart(icand)+NSPM/2)/fs tret=(nstart(icand)+NSPM/2)/fs

View File

@ -5,21 +5,22 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
! Analysis block size = NZ = 7168 samples, t_block = 0.597333 s ! Analysis block size = NZ = 7168 samples, t_block = 0.597333 s
! Called from hspec() at half-block increments, about 0.3 s ! Called from hspec() at half-block increments, about 0.3 s
use packjt77
parameter (NZ=7168) !Block size parameter (NZ=7168) !Block size
parameter (NSPM=864) !Number of samples per message frame parameter (NSPM=864) !Number of samples per message frame
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 (NSHMEM=50) !Number of recent SWL messages to remember parameter (NSHMEM=50) !Number of recent SWL messages to remember
character*4 decsym !"&" for mskspd or "^" for long averages character*4 decsym !"&" for mskspd or "^" for long averages
character*37 msgreceived !Decoded message character*37 msgreceived !Decoded message
character*22 msgrx22 !Sh messages are returned as 22chars
character*37 msglast,msglastswl !Used for dupechecking character*37 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*37 recent_shmsgs(NSHMEM)
character*22 recent_shmsgs(NSHMEM)
character*512 datadir character*512 datadir
complex cdat(NFFT1) !Analytic signal complex cdat(NFFT1) !Analytic signal
@ -30,7 +31,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
integer iavmask(8) integer iavmask(8)
integer iavpatterns(8,NPATTERNS) integer iavpatterns(8,NPATTERNS)
integer npkloc(10) integer npkloc(10)
integer nhasharray(NRECENT,NRECENT) integer nhasharray(MAXRECENT,MAXRECENT)
integer nsnrlast,nsnrlastswl integer nsnrlast,nsnrlastswl
real d(NFFT1) real d(NFFT1)
@ -54,17 +55,17 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
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,cdat,msglast,msglastswl, & save first,tsec0,nutc00,pnoise,cdat,msglast,msglastswl, &
nsnrlast,nsnrlastswl,recent_calls,nhasharray,recent_shmsgs nsnrlast,nsnrlastswl,nhasharray,recent_shmsgs
if(first) then if(first) then
tsec0=tsec tsec0=tsec
nutc00=nutc0 nutc00=nutc0
pnoise=-1.0 pnoise=-1.0
do i=1,nrecent do i=1,MAXRECENT
recent_calls(i)(1:12)=' ' recent_calls(i)(1:13)=' '
enddo enddo
do i=1,nshmem do i=1,nshmem
recent_shmsgs(i)(1:22)=' ' recent_shmsgs(i)(1:37)=' '
enddo enddo
msglast=' ' msglast=' '
msglastswl=' ' msglastswl=' '
@ -116,10 +117,11 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
! 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,ndecodesuccess,msgreceived,fc,fest,tdec,navg,ct, & call msk144spd(cdat,np,ntol,ndecodesuccess,msgreceived,fc,fest,tdec,navg,ct, &
softbits,recent_calls,nrecent) softbits)
if(ndecodesuccess.eq.0 .and. (bshmsg.or.bswl)) then if(ndecodesuccess.eq.0 .and. (bshmsg.or.bswl)) 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,ndecodesuccess,msgreceived,fc,fest,tdec,navg) ndecodesuccess,msgrx22,fc,fest,tdec,navg)
if( ndecodesuccess .ge. 1 ) msgreceived(1:22)=msgrx22
endif endif
if( ndecodesuccess .ge. 1 ) then if( ndecodesuccess .ge. 1 ) then
tdec=tsec+tdec tdec=tsec+tdec
@ -150,8 +152,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
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,softbits,msgreceived,ndecodesuccess, & call msk144decodeframe(ct,softbits,msgreceived,ndecodesuccess)
recent_calls,nrecent)
if(ndecodesuccess .gt. 0) then if(ndecodesuccess .gt. 0) then
tdec=tsec+xmc(iavg)*tframe tdec=tsec+xmc(iavg)*tframe
goto 900 goto 900
@ -192,7 +193,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
decsym=' & ' decsym=' & '
if( btrain ) decsym=' ^ ' if( btrain ) decsym=' ^ '
if( msgreceived(1:1).eq.'<') then if( bshdecode ) then
ncorrected=0 ncorrected=0
eyeopening=0.0 eyeopening=0.0
endif endif
@ -207,11 +208,17 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
msglast=msgreceived msglast=msgreceived
nsnrlast=nsnr nsnrlast=nsnr
if(.not. bshdecode) then if(.not. bshdecode) then
call update_hasharray(recent_calls,nrecent,nhasharray) call update_hasharray(nhasharray)
endif endif
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived, & if( .not.bshdecode ) then
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived(1:22), &
navg,ncorrected,eyeopening,char(0) navg,ncorrected,eyeopening,char(0)
1020 format(i6.6,i4,f5.1,i5,a4,a22,i2,i3,f5.1,a1) 1020 format(i6.6,i4,f5.1,i5,a4,a22,i2,i3,f5.1,a1)
else
write(line,1022) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived(1:22), &
navg,char(0)
1022 format(i6.6,i4,f5.1,i5,a4,a22,i2,a1)
endif
elseif(bswl .and. ndecodesuccess.ge.2) then elseif(bswl .and. ndecodesuccess.ge.2) then
seenb4=.false. seenb4=.false.
do i=1,nshmem do i=1,nshmem
@ -226,8 +233,8 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
if(bflag) then if(bflag) then
msglastswl=msgreceived msglastswl=msgreceived
nsnrlastswl=nsnr nsnrlastswl=nsnr
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived, & write(line,1022) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived, &
navg,ncorrected,eyeopening,char(0) navg,char(0)
endif endif
endif endif
999 tsec0=tsec 999 tsec0=tsec
@ -236,8 +243,8 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
end subroutine mskrtd end subroutine mskrtd
subroutine update_recent_shmsgs(message,msgs,nsize) subroutine update_recent_shmsgs(message,msgs,nsize)
character*22 msgs(nsize) character*37 msgs(nsize)
character*22 message character*37 message
logical*1 seen logical*1 seen
seen=.false. seen=.false.

View File

@ -1,12 +1,12 @@
subroutine update_hasharray(recent_calls,nrecent,nhasharray) subroutine update_hasharray(nhasharray)
character*12 recent_calls(nrecent) use packjt77
character*22 hashmsg character*22 hashmsg
integer nhasharray(nrecent,nrecent) integer nhasharray(MAXRECENT,MAXRECENT)
nhasharray=-1 nhasharray=-1
do i=1,nrecent do i=1,MAXRECENT
do j=i+1,nrecent do j=i+1,MAXRECENT
if( recent_calls(i)(1:1) .ne. ' ' .and. recent_calls(j)(1:1) .ne. ' ' ) then if( recent_calls(i)(1:1) .ne. ' ' .and. recent_calls(j)(1:1) .ne. ' ' ) then
hashmsg=trim(recent_calls(i))//' '//trim(recent_calls(j)) hashmsg=trim(recent_calls(i))//' '//trim(recent_calls(j))
call fmtmsg(hashmsg,iz) call fmtmsg(hashmsg,iz)