Changes to existing files needed to accommodate short (16ms) msk messages.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@6869 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
Steven Franke 2016-07-05 21:06:04 +00:00
parent c91111bf28
commit 268208a185
5 changed files with 60 additions and 22 deletions

View File

@ -322,6 +322,7 @@ set (wsjt_FSRCS
lib/degrade_snr.f90 lib/degrade_snr.f90
lib/demod64a.f90 lib/demod64a.f90
lib/detectmsk144.f90 lib/detectmsk144.f90
lib/detectmsk32.f90
lib/determ.f90 lib/determ.f90
lib/downsam9.f90 lib/downsam9.f90
lib/encode232.f90 lib/encode232.f90
@ -359,6 +360,7 @@ set (wsjt_FSRCS
lib/geniscat.f90 lib/geniscat.f90
lib/genmsk.f90 lib/genmsk.f90
lib/genmsk144.f90 lib/genmsk144.f90
lib/genmsk32.f90
lib/genmsk_short.f90 lib/genmsk_short.f90
lib/genqra64.f90 lib/genqra64.f90
lib/genwspr.f90 lib/genwspr.f90

View File

@ -11,12 +11,16 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
complex c(NSPM) complex c(NSPM)
complex ctmp(NFFT) complex ctmp(NFFT)
complex cb(42) !Complex waveform for sync word complex cb(42) !Complex waveform for sync word
complex cbr(42) !Complex waveform for reversed sync word
complex cfac,cca,ccb complex cfac,cca,ccb
complex cc(NPTS) complex cc(NPTS)
complex ccr(NPTS)
complex cc1(NPTS) complex cc1(NPTS)
complex cc2(NPTS) complex cc2(NPTS)
complex ccr1(NPTS)
complex ccr2(NPTS)
complex bb(6) complex bb(6)
integer s8(8),hardbits(144) integer s8(8),s8r(8),hardbits(144)
integer, dimension(1) :: iloc integer, dimension(1) :: iloc
integer*1 decoded(80) integer*1 decoded(80)
integer indices(MAXSTEPS) integer indices(MAXSTEPS)
@ -28,6 +32,7 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
real hannwindow(NPTS) real hannwindow(NPTS)
real rcw(12) real rcw(12)
real dd(NPTS) real dd(NPTS)
real ddr(NPTS)
real ferrs(MAXCAND) real ferrs(MAXCAND)
real pp(12) !Half-sine pulse shape real pp(12) !Half-sine pulse shape
real snrs(MAXCAND) real snrs(MAXCAND)
@ -40,6 +45,7 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
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 s8r/1,0,1,1,0,0,0,1/
save df,first,cb,fs,pi,twopi,dt,s8,rcw,pp,hannwindow,nmatchedfilter save df,first,cb,fs,pi,twopi,dt,s8,rcw,pp,hannwindow,nmatchedfilter
if(first) then if(first) then
@ -64,7 +70,7 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
hannwindow(i)=0.5*(1-cos(twopi*(i-1)/NPTS)) hannwindow(i)=0.5*(1-cos(twopi*(i-1)/NPTS))
enddo enddo
! define the sync word waveform ! define the sync word waveforms
s8=2*s8-1 s8=2*s8-1
cbq(1:6)=pp(7:12)*s8(1) cbq(1:6)=pp(7:12)*s8(1)
cbq(7:18)=pp*s8(3) cbq(7:18)=pp*s8(3)
@ -75,6 +81,16 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
cbi(25:36)=pp*s8(6) cbi(25:36)=pp*s8(6)
cbi(37:42)=pp(1:6)*s8(8) cbi(37:42)=pp(1:6)*s8(8)
cb=cmplx(cbi,cbq) 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
@ -160,7 +176,7 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
allmessages=char(0) allmessages=char(0)
lines=char(0) lines=char(0)
do ip=1,ndet !run through the candidates and try to sync/demod/decode do ip=1,1 !run through the candidates and try to sync/demod/decode
imid=times(ip)*fs imid=times(ip)*fs
if( imid .lt. NPTS/2 ) imid=NPTS/2 if( imid .lt. NPTS/2 ) imid=NPTS/2
if( imid .gt. n-NPTS/2 ) imid=n-NPTS/2 if( imid .gt. n-NPTS/2 ) imid=n-NPTS/2
@ -175,14 +191,27 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
! attempt frame synchronization ! attempt frame synchronization
! correlate with sync word waveforms ! correlate with sync word waveforms
cc=0 cc=0
ccr=0
cc1=0 cc1=0
cc2=0 cc2=0
ccr1=0
ccr2=0
do i=1,NPTS-(56*6+41) do i=1,NPTS-(56*6+41)
cc1(i)=sum(cdat(i:i+41)*conjg(cb)) cc1(i)=sum(cdat(i:i+41)*conjg(cb))
cc2(i)=sum(cdat(i+56*6:i+56*6+41)*conjg(cb)) cc2(i)=sum(cdat(i+56*6:i+56*6+41)*conjg(cb))
enddo enddo
cc=cc1+cc2 cc=cc1+cc2
dd=abs(cc1)*abs(cc2) dd=abs(cc1)*abs(cc2)
do i=1,NPTS-(32*6+41)
ccr1(i)=sum(cdat(i:i+41)*conjg(cbr))
ccr2(i)=sum(cdat(i+32*6:i+32*6+41)*conjg(cbr))
enddo
ccr=ccr1+ccr2
ddr=abs(ccr1)*abs(ccr2)
cmax=maxval(abs(cc))
crmax=maxval(abs(ccr))
ishort=0
if( crmax .gt. cmax ) ishort=1
! Find 6 largest peaks ! Find 6 largest peaks
do ipk=1,6 do ipk=1,6
@ -325,7 +354,7 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
ssig=sqrt(s2av-sav*sav) ssig=sqrt(s2av-sav*sav)
softbits=softbits/ssig softbits=softbits/ssig
sigma=0.65 sigma=0.75
lratio(1:48)=softbits(9:9+47) lratio(1:48)=softbits(9:9+47)
lratio(49:128)=softbits(65:65+80-1) lratio(49:128)=softbits(65:65+80-1)
lratio=exp(2.0*lratio/(sigma*sigma)) lratio=exp(2.0*lratio/(sigma*sigma))
@ -355,8 +384,8 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
else else
msgreceived=' ' msgreceived=' '
ndither=-99 ! -99 is bad hash flag ndither=-99 ! -99 is bad hash flag
! write(78,1001) nutc,t0,nsnr,ic,ipk,is,idf,iav,deltaf,fest,ferr,ferr2,ffin,bba,bbp,nbadsync1,nbadsync2, & write(78,1001) nutc,t0,nsnr,ic,ipk,is,idf,iav,deltaf,fest,ferr,ferr2,ffin,bba,bbp,nbadsync1,nbadsync2, &
! phase0,niterations,ndither,msgreceived phase0,niterations,ndither,msgreceived
endif endif
endif endif
enddo ! frame averaging loop enddo ! frame averaging loop
@ -368,10 +397,10 @@ subroutine detectmsk144(cbig,n,pchk_file,lines,nmessages,nutc)
ndither=-98 ndither=-98
999 continue 999 continue
if( nmessages .ge. 1 ) then if( nmessages .ge. 1 ) then
! write(78,1001) nutc,t0,nsnr,ic,ipk,is,idf,iav,deltaf,fest,ferr,ferr2,ffin,bba,bbp,nbadsync1,nbadsync2, & write(78,1001) nutc,t0,nsnr,ic,ipk,is,idf,iav,deltaf,fest,ferr,ferr2,ffin,bba,bbp,nbadsync1,nbadsync2, &
! phase0,niterations,ndither,msgreceived phase0,niterations,ndither,msgreceived
! call flush(78) call flush(78)
!1001 format(i6.6,f8.2,i5,i5,i5,i5,i5,i5,f8.2,f8.2,f8.2,f8.2,f8.2,f10.2,f8.2,i5,i5,f8.2,i5,i5,2x,a22) 1001 format(i6.6,f8.2,i5,i5,i5,i5,i5,i5,f8.2,f8.2,f8.2,f8.2,f8.2,f10.2,f8.2,i5,i5,f8.2,i5,i5,2x,a22)
exit exit
endif endif
enddo enddo

View File

@ -82,9 +82,9 @@ subroutine genmsk144(msg0,ichk,msgsent,i4tone,itype,pchk_file)
enddo enddo
if(message(1:1).eq.'<') then if(message(1:1).eq.'<') then
call genmsk_short(message,msgsent,ichk,i4tone,itype) call genmsk32(message,msgsent,ichk,i4tone,itype)
if(itype.lt.0) go to 999 if(itype.lt.0) go to 999
i4tone(36)=-35 i4tone(33)=-35
go to 999 go to 999
endif endif

View File

@ -1,6 +1,6 @@
subroutine msk144_decode(id2,npts,nutc,nprint,pchk_file,line) subroutine msk144_decode(id2,npts,nutc,nprint,pchk_file,line)
! Calls the experimental decoder for JTMSK 72ms ldpc messages ! Calls the experimental decoder for MSK 72ms/16ms messages
parameter (NMAX=30*12000) parameter (NMAX=30*12000)
parameter (NFFTMAX=512*1024) parameter (NFFTMAX=512*1024)
@ -10,7 +10,6 @@ subroutine msk144_decode(id2,npts,nutc,nprint,pchk_file,line)
complex c(NFFTMAX) !Complex (analytic) data complex c(NFFTMAX) !Complex (analytic) data
character*80 line(100) !Decodes passed back to caller character*80 line(100) !Decodes passed back to caller
character*512 pchk_file character*512 pchk_file
! equivalence (hist,d)
line(1:100)(1:1)=char(0) line(1:100)(1:1)=char(0)
@ -36,6 +35,16 @@ subroutine msk144_decode(id2,npts,nutc,nprint,pchk_file,line)
write(*,'(a80)') line(i) write(*,'(a80)') line(i)
enddo enddo
endif endif
if(line(1)(1:6).eq.' ') line(1)(1:1)=char(0)
if(nline .eq. 0) then
call detectmsk32(c,npts,line,nline,nutc)
endif
if( nprint .ne. 0 ) then
do i=1,nline
write(*,'(a80)') line(i)
enddo
endif
return return
end subroutine msk144_decode end subroutine msk144_decode

View File

@ -6,13 +6,11 @@ program msk144sim
real waveform(0:NMAX-1) real waveform(0:NMAX-1)
character arg*8,msg*22,msgsent*22,fname*40 character arg*8,msg*22,msgsent*22,fname*40
character*512 pchk_file character*512 pchk_file
character*3 rpt(0:7)
real wave(0:NMAX-1) !Simulated received waveform real wave(0:NMAX-1) !Simulated received waveform
real*8 twopi,freq,phi,dphi0,dphi1,dphi real*8 twopi,freq,phi,dphi0,dphi1,dphi
type(hdr) h !Header for .wav file type(hdr) h !Header for .wav file
integer*2 iwave(0:NMAX-1) integer*2 iwave(0:NMAX-1)
integer itone(144) !Message bits integer itone(144) !Message bits
data rpt /'26 ','27 ','28 ','R26','R27','R28','RRR','73 '/
pchk_file='./peg-128-80-reg3.pchk' pchk_file='./peg-128-80-reg3.pchk'
@ -40,14 +38,16 @@ program msk144sim
ichk=0 ichk=0
call genmsk144(msg,ichk,msgsent,itone,itype,pchk_file) call genmsk144(msg,ichk,msgsent,itone,itype,pchk_file)
twopi=8.d0*atan(1.d0) twopi=8.d0*atan(1.d0)
nsym=144
if( itone(33) .lt. 0 ) nsym=32
dphi0=twopi*(freq-500)/12000.0 dphi0=twopi*(freq-500)/12000.0
dphi1=twopi*(freq+500)/12000.0 dphi1=twopi*(freq+500)/12000.0
phi=0.0 phi=0.0
indx=0 indx=0
nreps=NMAX/(144*6) nreps=NMAX/(nsym*6)
do jrep=1,nreps do jrep=1,nreps
do i=1,144 do i=1,nsym
if( itone(i) .eq. 0 ) then if( itone(i) .eq. 0 ) then
dphi=dphi0 dphi=dphi0
else else
@ -86,8 +86,6 @@ program msk144sim
write(10) h,iwave !Save the .wav file write(10) h,iwave !Save the .wav file
close(10) close(10)
! call jtmsk_short(cwave,NMAX,msg)
enddo enddo
999 end program msk144sim 999 end program msk144sim