mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-10-30 20:40:28 -04:00 
			
		
		
		
	More progress on SWL mode. Needs testing.
git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@7437 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
		
							parent
							
								
									b8e7339e88
								
							
						
					
					
						commit
						b8cc894a57
					
				| @ -5,13 +5,11 @@ subroutine extractmessage144(decoded,msgreceived,nhashflag,recent_calls,nrecent) | ||||
| 
 | ||||
|   character*22 msgreceived | ||||
|   character*12 call1,call2 | ||||
|   character*12  recent_calls(nrecent) | ||||
|   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 | ||||
|  | ||||
| @ -96,7 +96,6 @@ subroutine msk144decodeframe(c,softbits,msgreceived,nsuccess,recent_calls,nrecen | ||||
| !  call timer('bpdec144 ',0) | ||||
|   call bpdecode144(llr,max_iterations,decoded,niterations) | ||||
| !  call timer('bpdec144 ',1) | ||||
| 
 | ||||
|   if( niterations .ge. 0.0 ) then | ||||
|     call extractmessage144(decoded,msgreceived,nhashflag,recent_calls,nrecent) | ||||
|     if( nhashflag .gt. 0 ) then  ! CRCs match, so print it  | ||||
|  | ||||
| @ -1,11 +1,12 @@ | ||||
| subroutine msk40decodeframe(c,mycall,hiscall,xsnr,msgreceived,     & | ||||
|                             nsuccess,bswl,nhasharray,nrecent) | ||||
| subroutine msk40decodeframe(c,mycall,hiscall,xsnr,bswl,nhasharray,             & | ||||
|                             recent_calls,nrecent,msgreceived,nsuccess) | ||||
| !  use timer_module, only: timer | ||||
| 
 | ||||
|   parameter (NSPM=240) | ||||
|   character*4 rpt(0:15) | ||||
|   character*6 mycall,hiscall,mycall0,hiscall0 | ||||
|   character*22 hashmsg,msgreceived | ||||
|   character*12 recent_calls(nrecent) | ||||
|   complex cb(42) | ||||
|   complex cfac,cca | ||||
|   complex c(NSPM) | ||||
| @ -19,6 +20,7 @@ subroutine msk40decodeframe(c,mycall,hiscall,xsnr,msgreceived,     & | ||||
|   real softbits(40) | ||||
|   real llr(32) | ||||
|   logical first | ||||
|   logical bswl | ||||
|   data first/.true./ | ||||
|   data s8r/1,0,1,1,0,0,0,1/ | ||||
|   data mycall0/'dummy'/,hiscall0/'dummy'/ | ||||
| @ -133,6 +135,20 @@ subroutine msk40decodeframe(c,mycall,hiscall,xsnr,msgreceived,     & | ||||
|       write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(mycall),   & | ||||
|                                     trim(hiscall),">",rpt(nrxrpt) | ||||
|       return | ||||
|     elseif(bswl .and. nhammd.le.4 .and. cord.lt.0.65) then | ||||
|       do i=1,nrecent | ||||
|         do j=i+1,nrecent | ||||
|           if( nrxhash .eq. nhasharray(i,j) ) then | ||||
|             nsuccess=1 | ||||
|             write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(recent_calls(i)),   & | ||||
|                                   trim(recent_calls(j)),">",rpt(nrxrpt) | ||||
|           elseif( nrxhash .eq. nhasharray(j,i) ) then | ||||
|             nsuccess=1 | ||||
|             write(msgreceived,'(a1,a,1x,a,a1,1x,a4)') "<",trim(recent_calls(j)),   & | ||||
|                                   trim(recent_calls(i)),">",rpt(nrxrpt) | ||||
|           endif | ||||
|         enddo | ||||
|       enddo | ||||
|     endif | ||||
|   endif | ||||
| 
 | ||||
|  | ||||
| @ -1,5 +1,5 @@ | ||||
| subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,   & | ||||
|                     fret,tret,navg,nhasharray,nrecent) | ||||
| subroutine msk40spd(cbig,n,ntol,mycall,hiscall,bswl,nhasharray,recent_calls,   & | ||||
|                     nrecent,nsuccess,msgreceived,fc,fret,tret,navg) | ||||
| ! msk40 short-ping-decoder | ||||
| 
 | ||||
|   use timer_module, only: timer | ||||
| @ -7,6 +7,7 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,   & | ||||
|   parameter (NSPM=240, MAXSTEPS=150, NFFT=NSPM, MAXCAND=5, NPATTERNS=6) | ||||
|   character*6 mycall,hiscall | ||||
|   character*22 msgreceived | ||||
|   character*12 recent_calls(nrecent) | ||||
|   complex cbig(n) | ||||
|   complex cdat(3*NSPM)                    !Analytic signal | ||||
|   complex c(NSPM) | ||||
| @ -20,6 +21,7 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,   & | ||||
|   integer nstart(MAXCAND) | ||||
|   integer nhasharray(nrecent,nrecent) | ||||
|   logical ismask(NFFT) | ||||
|   logical bswl | ||||
|   real detmet(-2:MAXSTEPS+3) | ||||
|   real detmet2(-2:MAXSTEPS+3) | ||||
|   real detfer(MAXSTEPS) | ||||
| @ -82,7 +84,6 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,   & | ||||
| 
 | ||||
| ! Coarse carrier frequency sync - seek tones at 2000 Hz and 4000 Hz in  | ||||
| ! squared signal spectrum. | ||||
| ! search range for coarse frequency error is +/- 100 Hz | ||||
| 
 | ||||
|     ctmp=ctmp**2 | ||||
|     ctmp(1:12)=ctmp(1:12)*rcw | ||||
| @ -169,7 +170,8 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,   & | ||||
|     xsnr=snrs(icand) | ||||
|     do iav=1,NPATTERNS | ||||
|       navmask=navpatterns(1:3,iav)  | ||||
|       call msk40sync(cdat,3,ntol0,deltaf,navmask,npeaks,fo,fest,npkloc,nsyncsuccess,c) | ||||
|       call msk40sync(cdat,3,ntol0,deltaf,navmask,npeaks,fo,fest,npkloc,       & | ||||
|                      nsyncsuccess,c) | ||||
|       if( nsyncsuccess .eq. 0 ) cycle | ||||
| 
 | ||||
|       do ipk=1,npeaks | ||||
| @ -178,9 +180,8 @@ subroutine msk40spd(cbig,n,ntol,mycall,hiscall,nsuccess,msgreceived,fc,   & | ||||
|           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,nhasharray,nrecent) | ||||
| 
 | ||||
|           call msk40decodeframe(ct,mycall,hiscall,xsnr,bswl,nhasharray,        & | ||||
|                                 recent_calls,nrecent,msgreceived,ndecodesuccess)    | ||||
|           if( ndecodesuccess .gt. 0 ) then | ||||
| !write(*,*) icand, iav, ipk, is, tret, fret, msgreceived | ||||
|             tret=(nstart(icand)+NSPM/2)/fs | ||||
|  | ||||
| @ -36,8 +36,9 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall,   & | ||||
|   real pcoeffs(3) | ||||
| 
 | ||||
|   logical*1 bshmsg,bcontest,brxequal,bswl | ||||
|   logical first | ||||
|   logical*1 first | ||||
|   logical*1 trained  | ||||
|   logical*1 bshdecode | ||||
|   | ||||
|   data first/.true./ | ||||
|   data iavpatterns/ & | ||||
| @ -46,7 +47,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,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,recent_calls,nhasharray | ||||
|   save first,tsec0,nutc00,pnoise,nsnrlast,msglast,cdat,pcoeffs,trained,       & | ||||
|        recent_calls,nhasharray | ||||
| 
 | ||||
|   if(first) then | ||||
|      tsec0=tsec | ||||
| @ -98,13 +100,12 @@ 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,recent_calls,nrecent) | ||||
| 
 | ||||
|   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,bswl,nhasharray,nrecent) | ||||
|      call msk40spd(cdat,np,ntol,mycall(1:6),hiscall(1:6),bswl,nhasharray,     & | ||||
|                    recent_calls,nrecent,nsuccess,msgreceived,fc,fest,tdec,navg) | ||||
|   endif | ||||
| 
 | ||||
|   if( nsuccess .eq. 1 ) then | ||||
|     tdec=tsec+tdec | ||||
|     ipk=0 | ||||
| @ -134,7 +135,7 @@ 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 | ||||
| @ -166,8 +167,13 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall,   & | ||||
|   endif | ||||
|   nsnr=nint(snr0) | ||||
| 
 | ||||
|   call msk144signalquality(ct,snr0,fest,tdec,softbits,msgreceived,hiscall,   & | ||||
|   bshdecode=.false. | ||||
|   if( msgreceived(1:1) .eq. '<' ) bshdecode=.true. | ||||
| 
 | ||||
|   if(.not. bshdecode) then | ||||
|     call msk144signalquality(ct,snr0,fest,tdec,softbits,msgreceived,hiscall,   & | ||||
|                            ncorrected,eyeopening,trained,pcoeffs) | ||||
|   endif | ||||
| 
 | ||||
| ! Dupe check. Only print if new message, or higher snr. | ||||
|   if(msgreceived.ne.msglast .or. nsnr.gt.nsnrlast .or. tsec.lt.tsec0) then | ||||
| @ -176,8 +182,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall,   & | ||||
|      nsnrlast=nsnr | ||||
|      if( nsnr .lt. -8 ) nsnr=-8 | ||||
|      if( nsnr .gt. 24 ) nsnr=24 | ||||
| !     if(bcontest .and. msgreceived(1:1).ne.'<') then | ||||
|      if(msgreceived(1:1).ne.'<') then | ||||
|      if(.not. bshdecode) then | ||||
|         call fix_contest_msg(mycall(1:6),mygrid,hiscall(1:6),msgreceived) | ||||
|      endif | ||||
|      decsym=' & ' | ||||
|  | ||||
| @ -7,16 +7,18 @@ subroutine update_hasharray(recent_calls,nrecent,nhasharray) | ||||
|   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 | ||||
|       if( recent_calls(i) .ne. '  ' .and. recent_calls(j) .ne. '  ' ) then | ||||
|         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 | ||||
|       endif | ||||
|     enddo | ||||
|   enddo  | ||||
| 
 | ||||
|  | ||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user