mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-11-03 21:40:52 -05:00 
			
		
		
		
	All types of Q65 message averaging are now implemented and functional.
This commit is contained in:
		
							parent
							
								
									b64c1faba4
								
							
						
					
					
						commit
						ada5a60124
					
				@ -61,7 +61,6 @@ contains
 | 
			
		||||
    integer*2 iwave(NMAX)                 !Raw data
 | 
			
		||||
    real, allocatable :: dd(:)            !Raw data
 | 
			
		||||
    integer dat4(13)                      !Decoded message as 12 6-bit integers
 | 
			
		||||
    integer apmask1(78),apsymbols1(78)
 | 
			
		||||
    integer dgen(13)
 | 
			
		||||
    logical lclearave,lapcqonly,unpk77_success
 | 
			
		||||
    complex, allocatable :: c00(:)        !Analytic signal, 6000 Sa/s
 | 
			
		||||
@ -165,38 +164,31 @@ contains
 | 
			
		||||
       if(idec.ge.0) go to 100       !Successful decode, we're done
 | 
			
		||||
    enddo  ! ipass
 | 
			
		||||
 | 
			
		||||
    if(iand(ndepth,16).eq.16) then
 | 
			
		||||
    if(iand(ndepth,16).eq.0 .or. navg.lt.2) go to 100
 | 
			
		||||
! There was no single-transmission decode. Try for an average 'q3n' decode.
 | 
			
		||||
       call timer('list_avg',0)
 | 
			
		||||
    call timer('list_avg',0)
 | 
			
		||||
! Call top-level routine in q65 module: establish sync and try for a q3
 | 
			
		||||
! decode, this time using the cumulative 's1a' symbol spectra.
 | 
			
		||||
       iavg=1
 | 
			
		||||
       call q65_dec0(iavg,nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave,  &
 | 
			
		||||
            emedelay,xdt,f0,snr1,width,dat4,snr2,idec)
 | 
			
		||||
       call timer('list_avg',1)
 | 
			
		||||
       if(idec.ge.0) then
 | 
			
		||||
          nused=navg
 | 
			
		||||
          go to 100
 | 
			
		||||
       endif
 | 
			
		||||
    iavg=1
 | 
			
		||||
    call q65_dec0(iavg,nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave,  &
 | 
			
		||||
         emedelay,xdt,f0,snr1,width,dat4,snr2,idec)
 | 
			
		||||
    call timer('list_avg',1)
 | 
			
		||||
    if(idec.ge.0) then
 | 
			
		||||
       nused=navg
 | 
			
		||||
       go to 100
 | 
			
		||||
    endif
 | 
			
		||||
 | 
			
		||||
! There was no 'q3n' decode.  Try for a 'q[012]n' decode.
 | 
			
		||||
       do ipass=0,npasses                  !Loop over AP passes
 | 
			
		||||
          apmask=0                         !Try first with no AP information
 | 
			
		||||
          apsymbols=0
 | 
			
		||||
          if(ipass.ge.1) then
 | 
			
		||||
          ! Subsequent passes use AP information appropiate for nQSOprogress
 | 
			
		||||
             call q65_ap(nQSOprogress,ipass,ncontest,lapcqonly,iaptype,   &
 | 
			
		||||
                  apsym0,apmask1,apsymbols1)
 | 
			
		||||
             write(c78,1050) apmask1
 | 
			
		||||
             read(c78,1060) apmask
 | 
			
		||||
             write(c78,1050) apsymbols1
 | 
			
		||||
             read(c78,1060) apsymbols
 | 
			
		||||
          endif
 | 
			
		||||
!          call q65_dec012()    
 | 
			
		||||
          if(idec.ge.0) go to 100       !Successful decode, we're done
 | 
			
		||||
       enddo
 | 
			
		||||
    endif
 | 
			
		||||
    
 | 
			
		||||
! Call top-level routine in q65 module: establish sync and try for a q[012]n
 | 
			
		||||
! decode, this time using the cumulative 's1a' symbol spectra.
 | 
			
		||||
 | 
			
		||||
    call timer('q65_avg ',0)
 | 
			
		||||
    iavg=2
 | 
			
		||||
    call q65_dec0(iavg,nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave,  &
 | 
			
		||||
         emedelay,xdt,f0,snr1,width,dat4,snr2,idec)
 | 
			
		||||
    call timer('q65_avg ',1)
 | 
			
		||||
     if(idec.ge.0) nused=navg
 | 
			
		||||
 | 
			
		||||
100 decoded='                                     '
 | 
			
		||||
    if(idec.ge.0) then
 | 
			
		||||
! idec Meaning
 | 
			
		||||
@ -217,6 +209,7 @@ contains
 | 
			
		||||
    else
 | 
			
		||||
! Report snr1, even if no decode.
 | 
			
		||||
       nsnr=db(snr1) - 35.0
 | 
			
		||||
       if(nsnr.lt.-35) nsnr=-35
 | 
			
		||||
       idec=-1
 | 
			
		||||
       call this%callback(nutc,snr1,nsnr,xdt1,f1,decoded,              &
 | 
			
		||||
            idec,navg,ntrperiod)
 | 
			
		||||
 | 
			
		||||
@ -5,11 +5,13 @@ module q65
 | 
			
		||||
  integer nsave,nlist,LL0
 | 
			
		||||
  integer listutc(10)
 | 
			
		||||
  integer apsym0(58),aph10(10)
 | 
			
		||||
  integer apmask1(78),apsymbols1(78)
 | 
			
		||||
  integer apmask(13),apsymbols(13)
 | 
			
		||||
  integer,dimension(22) ::  isync = (/1,9,12,13,15,22,23,26,27,33,35,   &
 | 
			
		||||
                                     38,46,50,55,60,62,66,69,74,76,85/)
 | 
			
		||||
  integer codewords(63,206)
 | 
			
		||||
  integer navg,ibwa,ibwb,ncw,nsps,mode_q65,istep,nsmo,lag1,lag2
 | 
			
		||||
  integer navg,ibwa,ibwb,ncw,nsps,mode_q65
 | 
			
		||||
  integer istep,nsmo,lag1,lag2,npasses,nused
 | 
			
		||||
  integer i0,j0
 | 
			
		||||
  real,allocatable,save :: s1a(:,:)      !Cumulative symbol spectra
 | 
			
		||||
  real sync(85)                          !sync vector
 | 
			
		||||
@ -96,6 +98,7 @@ subroutine q65_dec0(iavg,nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave,  &
 | 
			
		||||
     s1a=0.
 | 
			
		||||
     navg=0
 | 
			
		||||
     LL0=LL
 | 
			
		||||
     lclearave=.false.
 | 
			
		||||
  endif
 | 
			
		||||
  dtstep=nsps/(NSTEP*12000.0)                 !Step size in seconds
 | 
			
		||||
  lag1=-1.0/dtstep
 | 
			
		||||
@ -113,7 +116,7 @@ subroutine q65_dec0(iavg,nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave,  &
 | 
			
		||||
  else
 | 
			
		||||
     s1=s1a
 | 
			
		||||
  endif
 | 
			
		||||
 | 
			
		||||
  
 | 
			
		||||
  i0=nint(nfqso/df)                             !Target QSO frequency
 | 
			
		||||
  if(i0-64.lt.1 .or. i0-65+LL.gt.iz) go to 900  !Frequency out of range
 | 
			
		||||
  call pctile(s1(i0-64:i0-65+LL,1:jz),LL*jz,40,base)
 | 
			
		||||
@ -127,7 +130,7 @@ subroutine q65_dec0(iavg,nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave,  &
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
  dat4=0
 | 
			
		||||
  if(ncw.gt.0) then
 | 
			
		||||
  if(ncw.gt.0 .and. iavg.lt.2) then
 | 
			
		||||
! Try list decoding via "Deep Likelihood".
 | 
			
		||||
     call timer('ccf_85  ',0)
 | 
			
		||||
! Try to synchronize using all 85 symbols
 | 
			
		||||
@ -196,6 +199,10 @@ subroutine q65_dec0(iavg,nutc,iwave,ntrperiod,nfqso,ntol,ndepth,lclearave,  &
 | 
			
		||||
  enddo
 | 
			
		||||
  close(17)
 | 
			
		||||
 | 
			
		||||
  if(iavg.eq.2) then
 | 
			
		||||
     call q65_dec_q012(s3,LL,snr2,dat4,idec,decoded)
 | 
			
		||||
  endif
 | 
			
		||||
  
 | 
			
		||||
900 return
 | 
			
		||||
end subroutine q65_dec0
 | 
			
		||||
  
 | 
			
		||||
@ -287,6 +294,56 @@ subroutine q65_dec_q3(s1,iz,jz,s3,LL,ipk,jpk,snr2,dat4,idec,decoded)
 | 
			
		||||
  return
 | 
			
		||||
end subroutine q65_dec_q3
 | 
			
		||||
 | 
			
		||||
subroutine q65_dec_q012(s3,LL,snr2,dat4,idec,decoded)
 | 
			
		||||
 | 
			
		||||
  character*37 decoded
 | 
			
		||||
  character*78 c78
 | 
			
		||||
  integer dat4(13)
 | 
			
		||||
  real s3(-64:LL-65,63)
 | 
			
		||||
  logical lapcqonly
 | 
			
		||||
 | 
			
		||||
  nsubmode=0
 | 
			
		||||
  if(mode_q65.eq.2) nsubmode=1
 | 
			
		||||
  if(mode_q65.eq.4) nsubmode=2
 | 
			
		||||
  if(mode_q65.eq.8) nsubmode=3
 | 
			
		||||
  if(mode_q65.eq.16) nsubmode=4
 | 
			
		||||
  
 | 
			
		||||
  baud=12000.0/nsps
 | 
			
		||||
  iaptype=0
 | 
			
		||||
  nQSOprogress=0    !### TEMPORARY  ? ###
 | 
			
		||||
  ncontest=0
 | 
			
		||||
  lapcqonly=.false.
 | 
			
		||||
  
 | 
			
		||||
  do ipass=0,npasses                  !Loop over AP passes
 | 
			
		||||
     apmask=0                         !Try first with no AP information
 | 
			
		||||
     apsymbols=0
 | 
			
		||||
     if(ipass.ge.1) then
 | 
			
		||||
        ! Subsequent passes use AP information appropiate for nQSOprogress
 | 
			
		||||
        call q65_ap(nQSOprogress,ipass,ncontest,lapcqonly,iaptype,   &
 | 
			
		||||
             apsym0,apmask1,apsymbols1)
 | 
			
		||||
        write(c78,1050) apmask1
 | 
			
		||||
1050    format(78i1)
 | 
			
		||||
        read(c78,1060) apmask
 | 
			
		||||
1060    format(13b6.6)
 | 
			
		||||
        write(c78,1050) apsymbols1
 | 
			
		||||
        read(c78,1060) apsymbols
 | 
			
		||||
     endif
 | 
			
		||||
 | 
			
		||||
     do ibw=ibwa,ibwb
 | 
			
		||||
        b90=1.72**ibw
 | 
			
		||||
        b90ts=b90/baud
 | 
			
		||||
        call q65_dec2(s3,nsubmode,b90ts,esnodb,irc,dat4,decoded)
 | 
			
		||||
        if(irc.ge.0) then
 | 
			
		||||
           snr2=esnodb - db(2500.0/baud) + 3.0     !Empirical adjustment
 | 
			
		||||
           idec=iaptype
 | 
			
		||||
           go to 100
 | 
			
		||||
        endif
 | 
			
		||||
     enddo
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
100 return
 | 
			
		||||
end subroutine q65_dec_q012
 | 
			
		||||
 | 
			
		||||
subroutine q65_ccf_85(s1,iz,jz,nfqso,ia,ia2,  &
 | 
			
		||||
     ipk,jpk,f0,xdt,imsg_best,ccf,ccf1)
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user