Progress toward SWL capability. Not finished and not tested.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@7434 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
Steven Franke 2016-12-31 02:05:51 +00:00
parent 33628fd9f4
commit 077ac1d77b
12 changed files with 216 additions and 21 deletions

View File

@ -468,6 +468,9 @@ set (wsjt_FSRCS
lib/tweak1.f90
lib/twkfreq.f90
lib/twkfreq65.f90
lib/unpackmsg144.f90
lib/update_recent_calls.f90
lib/update_hasharray.f90
lib/wav11.f90
lib/wav12.f90
lib/wavhdr.f90

View File

@ -1,14 +1,18 @@
subroutine extractmessage144(decoded,msgreceived,nhashflag)
subroutine extractmessage144(decoded,msgreceived,nhashflag,recent_calls,nrecent)
use iso_c_binding, only: c_loc,c_size_t
use packjt
use hashing
character*22 msgreceived
character*12 call1,call2
character*12 recent_calls(nrecent)
integer*1 decoded(80)
integer*1, target:: i1Dec8BitBytes(10)
integer*1 i1hashdec
integer*4 i4Dec6BitWords(12)
logical first
data first/.true./
! Collapse 80 decoded bits to 10 bytes. Bytes 1-9 are the message, byte 10 is the hash
do ibyte=1,10
itmp=0
@ -33,8 +37,14 @@ subroutine extractmessage144(decoded,msgreceived,nhashflag)
enddo
i4Dec6BitWords(ibyte)=itmp
enddo
call unpackmsg(i4Dec6BitWords,msgreceived)
call unpackmsg144(i4Dec6BitWords,msgreceived,call1,call2)
nhashflag=1
if( call1(1:2) .ne. 'CQ' .and. call1(1:2) .ne. ' ' ) then
call update_recent_calls(call1,recent_calls,nrecent)
endif
if( call2(1:2) .ne. ' ' ) then
call update_recent_calls(call2,recent_calls,nrecent)
endif
else
msgreceived=' '
nhashflag=-1

View File

@ -1,5 +1,5 @@
subroutine hspec(id2,k,nutc0,ntrpdepth,nrxfreq,ntol,bmsk144,bcontest, &
brxequal,ingain,mycall,hiscall,bshmsg,green,s,jh,line1,mygrid)
brxequal,ingain,mycall,hiscall,bshmsg,bswl,green,s,jh,line1,mygrid)
! Input:
! k pointer to the most recent new data
@ -21,7 +21,7 @@ subroutine hspec(id2,k,nutc0,ntrpdepth,nrxfreq,ntol,bmsk144,bcontest, &
character*12 mycall,hiscall
character*6 mygrid
integer*2 id2(0:120*12000-1)
logical*1 bmsk144,bcontest,bshmsg,brxequal
logical*1 bmsk144,bcontest,bshmsg,brxequal,bswl
real green(0:JZ-1)
real s(0:63,0:JZ-1)
real x(512)
@ -84,7 +84,7 @@ subroutine hspec(id2,k,nutc0,ntrpdepth,nrxfreq,ntol,bmsk144,bcontest, &
tt2=sum(float(abs(id2(k0:k0+3583))))
if(tt1.ne.0.0 .and. tt2.ne.0) then
call mskrtd(id2(k-7168+1:k),nutc0,tsec,ntol,nrxfreq,ndepth, &
mycall,mygrid,hiscall,bshmsg,bcontest,brxequal,line1)
mycall,mygrid,hiscall,bshmsg,bcontest,brxequal,bswl,line1)
endif
endif
endif

View File

@ -1,8 +1,9 @@
subroutine msk144decodeframe(c,softbits,msgreceived,nsuccess)
subroutine msk144decodeframe(c,softbits,msgreceived,nsuccess,recent_calls,nrecent)
! use timer_module, only: timer
parameter (NSPM=864)
character*22 msgreceived
character*12 recent_calls(nrecent)
complex cb(42)
complex cfac,cca,ccb
complex c(NSPM)
@ -97,7 +98,7 @@ subroutine msk144decodeframe(c,softbits,msgreceived,nsuccess)
! call timer('bpdec144 ',1)
if( niterations .ge. 0.0 ) then
call extractmessage144(decoded,msgreceived,nhashflag)
call extractmessage144(decoded,msgreceived,nhashflag,recent_calls,nrecent)
if( nhashflag .gt. 0 ) then ! CRCs match, so print it
nsuccess=1
endif

View File

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

View File

@ -1,4 +1,5 @@
subroutine msk40decodeframe(c,mycall,hiscall,xsnr,msgreceived,nsuccess)
subroutine msk40decodeframe(c,mycall,hiscall,xsnr,msgreceived, &
nsuccess,bswl,nhasharray,nrecent)
! use timer_module, only: timer
parameter (NSPM=240)
@ -11,6 +12,7 @@ subroutine msk40decodeframe(c,mycall,hiscall,xsnr,msgreceived,nsuccess)
integer*1 cw(32)
integer*1 decoded(16)
integer s8r(8),hardbits(40)
integer nhasharray(nrecent,nrecent)
real*8 dt, fs, pi, twopi
real cbi(42),cbq(42)
real pp(12)

View File

@ -1,4 +1,5 @@
subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,fret,tret,navg)
subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc, &
fret,tret,navg,nhasharray,nrecent)
! msk40 short-ping-decoder
use timer_module, only: timer
@ -17,6 +18,7 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,fret,tret
integer navpatterns(3,NPATTERNS)
integer navmask(3)
integer nstart(MAXCAND)
integer nhasharray(nrecent,nrecent)
logical ismask(NFFT)
real detmet(-2:MAXSTEPS+3)
real detmet2(-2:MAXSTEPS+3)
@ -176,7 +178,8 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,fret,tret
if( is.eq.2) ic0=max(1,ic0-1)
if( is.eq.3) ic0=min(NSPM,ic0+1)
ct=cshift(c,ic0-1)
call msk40decodeframe(ct,mycall,hiscall,xsnr,msgreceived,ndecodesuccess)
call msk40decodeframe(ct,mycall,hiscall,xsnr,msgreceived, &
ndecodesuccess,nhasharray,nrecent)
if( ndecodesuccess .gt. 0 ) then
!write(*,*) icand, iav, ipk, is, tret, fret, msgreceived

View File

@ -1,5 +1,5 @@
subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
bshmsg,bcontest,brxequal,line)
bshmsg,bcontest,brxequal,bswl,line)
! Real-time decoder for MSK144.
! Analysis block size = NZ = 7168 samples, t_block = 0.597333 s
@ -9,6 +9,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
parameter (NSPM=864) !Number of samples per message frame
parameter (NFFT1=8192) !FFT size for making analytic signal
parameter (NPATTERNS=4) !Number of frame averaging patterns to try
parameter (NRECENT=10) !Number of recent calls to remember
character*3 decsym !"&" for mskspd or "^" for long averages
character*22 msgreceived !Decoded message
@ -16,6 +17,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
character*80 line !Formatted line with UTC dB T Freq Msg
character*12 mycall,hiscall
character*6 mygrid
character*12 recent_calls(NRECENT)
complex cdat(NFFT1) !Analytic signal
complex c(NSPM) !Coherently averaged complex data
@ -25,6 +27,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
integer iavmask(8)
integer iavpatterns(8,NPATTERNS)
integer npkloc(10)
integer nhasharray(NRECENT,NRECENT)
real d(NFFT1)
real pow(8)
@ -32,7 +35,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
real xmc(NPATTERNS)
real pcoeffs(3)
logical*1 bshmsg,bcontest,brxequal
logical*1 bshmsg,bcontest,brxequal,bswl
logical first
logical*1 trained
@ -43,13 +46,16 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
1,1,1,1,1,0,0,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
save first,tsec0,nutc00,pnoise,nsnrlast,msglast,cdat,pcoeffs,trained
save first,tsec0,nutc00,pnoise,nsnrlast,msglast,cdat,pcoeffs,trained,recent_calls,nhasharray
if(first) then
tsec0=tsec
nutc00=nutc0
pnoise=-1.0
pcoeffs(1:3)=0.0
do i=1,nrecent
recent_calls(i)(1:12)=' '
enddo
trained=.false.
first=.false.
endif
@ -92,11 +98,11 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
! center a 3-frame analysis window and attempts to decode each of the
! 3 frames along with 2- and 3-frame averages.
np=8*NSPM
call msk144spd(cdat,np,ntol,nsuccess,msgreceived,fc,fest,tdec,navg,ct,softbits)
call msk144spd(cdat,np,ntol,nsuccess,msgreceived,fc,fest,tdec,navg,ct,softbits,recent_calls,nrecent)
if(nsuccess.eq.0 .and. bshmsg) then
call msk40spd(cdat,np,ntol,mycall(1:6),hiscall(1:6),nsuccess, &
msgreceived,fc,fest,tdec,navg)
msgreceived,fc,fest,tdec,navg,bswl,nhasharray,nrecent)
endif
if( nsuccess .eq. 1 ) then
@ -128,7 +134,8 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
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,softbits,msgreceived,ndecodesuccess)
call msk144decodeframe(ct,softbits,msgreceived,ndecodesuccess, &
recent_calls,nrecent)
if(ndecodesuccess .gt. 0) then
tdec=tsec+xmc(iavg)*tframe
goto 900
@ -164,6 +171,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
! Dupe check. Only print if new message, or higher snr.
if(msgreceived.ne.msglast .or. nsnr.gt.nsnrlast .or. tsec.lt.tsec0) then
call update_hasharray(recent_calls,nrecent,nhasharray)
msglast=msgreceived
nsnrlast=nsnr
if( nsnr .lt. -8 ) nsnr=-8
@ -176,6 +184,10 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
if( brxequal .and. (.not. trained) ) decsym=' ^ '
if( brxequal .and. trained ) decsym=' $ '
if( (.not. brxequal) .and. trained ) decsym=' @ '
if( msgreceived(1:1).eq.'<') then
ncorrected=0
eyeopening=0.0
endif
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived, &
navg,ncorrected,eyeopening,char(0)
1020 format(i6.6,i4,f5.1,i5,a3,a22,i2,i3,f5.1,a1)

117
lib/unpackmsg144.f90 Normal file
View File

@ -0,0 +1,117 @@
subroutine unpackmsg144(dat,msg,c1,c2)
! special unpackmsg for MSK144 - returns call1 and call2 to enable
! maintenance of a recent-calls-heard list
use packjt
parameter (NBASE=37*36*10*27*27*27)
parameter (NGBASE=180*180)
integer dat(12)
character c1*12,c2*12,grid*4,msg*22,grid6*6,psfx*4,junk2*4
logical cqnnn
cqnnn=.false.
nc1=ishft(dat(1),22) + ishft(dat(2),16) + ishft(dat(3),10)+ &
ishft(dat(4),4) + iand(ishft(dat(5),-2),15)
nc2=ishft(iand(dat(5),3),26) + ishft(dat(6),20) + &
ishft(dat(7),14) + ishft(dat(8),8) + ishft(dat(9),2) + &
iand(ishft(dat(10),-4),3)
ng=ishft(iand(dat(10),15),12) + ishft(dat(11),6) + dat(12)
if(ng.ge.32768) then
call unpacktext(nc1,nc2,ng,msg)
c1(1:12)=' '
c2(1:12)=' '
go to 100
endif
call unpackcall(nc1,c1,iv2,psfx)
if(iv2.eq.0) then
! This is an "original JT65" message
if(nc1.eq.NBASE+1) c1='CQ '
if(nc1.eq.NBASE+2) c1='QRZ '
nfreq=nc1-NBASE-3
if(nfreq.ge.0 .and. nfreq.le.999) then
write(c1,1002) nfreq
1002 format('CQ ',i3.3)
cqnnn=.true.
endif
endif
call unpackcall(nc2,c2,junk1,junk2)
call unpackgrid(ng,grid)
if(iv2.gt.0) then
! This is a JT65v2 message
do i=1,4
if(ichar(psfx(i:i)).eq.0) psfx(i:i)=' '
enddo
n1=len_trim(psfx)
n2=len_trim(c2)
if(iv2.eq.1) msg='CQ '//psfx(:n1)//'/'//c2(:n2)//' '//grid
if(iv2.eq.2) msg='QRZ '//psfx(:n1)//'/'//c2(:n2)//' '//grid
if(iv2.eq.3) msg='DE '//psfx(:n1)//'/'//c2(:n2)//' '//grid
if(iv2.eq.4) msg='CQ '//c2(:n2)//'/'//psfx(:n1)//' '//grid
if(iv2.eq.5) msg='QRZ '//c2(:n2)//'/'//psfx(:n1)//' '//grid
if(iv2.eq.6) msg='DE '//c2(:n2)//'/'//psfx(:n1)//' '//grid
if(iv2.eq.7) msg='DE '//c2(:n2)//' '//grid
if(iv2.eq.8) msg=' '
go to 100
else
endif
grid6=grid//'ma'
call grid2k(grid6,k)
if(k.ge.1 .and. k.le.450) call getpfx2(k,c1)
if(k.ge.451 .and. k.le.900) call getpfx2(k,c2)
i=index(c1,char(0))
if(i.ge.3) c1=c1(1:i-1)//' '
i=index(c2,char(0))
if(i.ge.3) c2=c2(1:i-1)//' '
msg=' '
j=0
if(cqnnn) then
msg=c1//' '
j=7 !### ??? ###
go to 10
endif
do i=1,12
j=j+1
msg(j:j)=c1(i:i)
if(c1(i:i).eq.' ') go to 10
enddo
j=j+1
msg(j:j)=' '
10 do i=1,12
if(j.le.21) j=j+1
msg(j:j)=c2(i:i)
if(c2(i:i).eq.' ') go to 20
enddo
if(j.le.21) j=j+1
msg(j:j)=' '
20 if(k.eq.0) then
do i=1,4
if(j.le.21) j=j+1
msg(j:j)=grid(i:i)
enddo
if(j.le.21) j=j+1
msg(j:j)=' '
endif
100 continue
if(msg(1:6).eq.'CQ9DX ') msg(3:3)=' '
if(msg(1:2).eq.'E9' .and. &
msg(3:3).ge.'A' .and. msg(3:3).le.'Z' .and. &
msg(4:4).ge.'A' .and. msg(4:4).le.'Z' .and. &
msg(5:5).eq.' ') msg='CQ '//msg(3:)
return
end subroutine unpackmsg144

23
lib/update_hasharray.f90 Normal file
View File

@ -0,0 +1,23 @@
subroutine update_hasharray(recent_calls,nrecent,nhasharray)
character*12 recent_calls(nrecent)
character*22 hashmsg
integer nhasharray(nrecent,nrecent)
nhasharray=-1
do i=1,nrecent
do j=i+1,nrecent
hashmsg=trim(recent_calls(i))//' '//trim(recent_calls(j))
call fmtmsg(hashmsg,iz)
call hash(hashmsg,22,ihash)
ihash=iand(ihash,4095)
nhasharray(i,j)=ihash
hashmsg=trim(recent_calls(j))//' '//trim(recent_calls(i))
call fmtmsg(hashmsg,iz)
call hash(hashmsg,22,ihash)
ihash=iand(ihash,4095)
nhasharray(j,i)=ihash
enddo
enddo
end subroutine update_hasharray

View File

@ -0,0 +1,19 @@
subroutine update_recent_calls(call,calls_hrd,nsize)
character*12 call,calls_hrd(nsize)
new=1
do ic=1,nsize
if( calls_hrd(ic).eq.call ) then
new=0
endif
enddo
if( new.eq.1 ) then
do ic=nsize-1,1,-1
calls_hrd(ic+1)(1:12)=calls_hrd(ic)(1:12)
enddo
calls_hrd(1)(1:12)=call(1:12)
endif
return
end subroutine update_recent_calls

View File

@ -68,7 +68,7 @@ extern "C" {
void hspec_(short int d2[], int* k, int* nutc0, int* ntrperiod, int* nrxfreq, int* ntol,
bool* bmsk144, bool* bcontest, bool* brxequalize, int* ingain, char mycall[],
char hiscall[], bool* bshmsg, float green[], float s[], int* jh,
char hiscall[], bool* bshmsg, bool* bswl, float green[], float s[], int* jh,
char line[], char mygrid[], int len1, int len2, int len3, int len4);
void gen4_(char* msg, int* ichk, char* msgsent, int itone[],
@ -1306,10 +1306,11 @@ void MainWindow::fastSink(qint64 frames)
bool bshmsg=ui->cbShMsgs->isChecked();
bool bcontest=m_config.contestMode();
bool brxequalize=m_config.rxEqualize();
bool bswl=ui->cbSWL->isChecked();
strncpy(dec_data.params.hiscall,(hisCall + " ").toLatin1 ().constData (), 12);
strncpy(dec_data.params.mygrid, (m_config.my_grid()+" ").toLatin1(),6);
hspec_(dec_data.d2,&k,&nutc0,&nTRpDepth,&m_RxFreq,&m_Ftol,&bmsk144,&bcontest,&brxequalize,
&m_inGain,&dec_data.params.mycall[0],&dec_data.params.hiscall[0],&bshmsg,
&m_inGain,&dec_data.params.mycall[0],&dec_data.params.hiscall[0],&bshmsg,&bswl,
fast_green,fast_s,&fast_jh,&line[0],&dec_data.params.mygrid[0],12,12,80,6);
float px = fast_green[fast_jh];
QString t;