mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-11-04 05:50:31 -05:00 
			
		
		
		
	Rearrange some FT8 code for consistency with other modes.
git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@7741 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
		
							parent
							
								
									7e62880e2a
								
							
						
					
					
						commit
						41336209c8
					
				@ -389,7 +389,7 @@ contains
 | 
			
		||||
    end select
 | 
			
		||||
  end subroutine jt9_decoded
 | 
			
		||||
 | 
			
		||||
    subroutine ft8_decoded (this, sync, snr, dt, freq, drift, decoded)
 | 
			
		||||
    subroutine ft8_decoded (this,sync,snr,dt,freq,nbadcrc,decoded)
 | 
			
		||||
    use ft8_decode
 | 
			
		||||
    implicit none
 | 
			
		||||
 | 
			
		||||
@ -398,20 +398,26 @@ contains
 | 
			
		||||
    integer, intent(in) :: snr
 | 
			
		||||
    real, intent(in) :: dt
 | 
			
		||||
    real, intent(in) :: freq
 | 
			
		||||
    integer, intent(in) :: drift
 | 
			
		||||
    integer, intent(in) :: nbadcrc
 | 
			
		||||
    character(len=22), intent(in) :: decoded
 | 
			
		||||
 | 
			
		||||
    !$omp critical(decode_results)
 | 
			
		||||
    write(*,1000) params%nutc,snr,dt,nint(freq),decoded
 | 
			
		||||
1000 format(i4.4,i4,f5.1,i5,1x,'@ ',1x,a22)
 | 
			
		||||
    write(13,1002) params%nutc,nint(sync),snr,dt,freq,drift,decoded
 | 
			
		||||
1002 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a22,' FT8')
 | 
			
		||||
    call flush(6)
 | 
			
		||||
    !$omp end critical(decode_results)
 | 
			
		||||
!###    !$omp critical(decode_results)
 | 
			
		||||
    if(nbadcrc.eq.0) then
 | 
			
		||||
       write(*,1000) params%nutc,snr,dt,nint(freq),decoded
 | 
			
		||||
1000   format(i6.6,i4,f5.1,i5,' ~ ',1x,a22)
 | 
			
		||||
       write(13,1002) params%nutc,nint(sync),snr,dt,freq,0,decoded
 | 
			
		||||
1002   format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a22,' FT8')
 | 
			
		||||
       call flush(6)
 | 
			
		||||
       call flush(13)
 | 
			
		||||
    endif
 | 
			
		||||
!###    !$omp end critical(decode_results)
 | 
			
		||||
    
 | 
			
		||||
    select type(this)
 | 
			
		||||
    type is (counting_ft8_decoder)
 | 
			
		||||
       this%decoded = this%decoded + 1
 | 
			
		||||
    end select
 | 
			
		||||
 | 
			
		||||
    return
 | 
			
		||||
  end subroutine ft8_decoded
 | 
			
		||||
 | 
			
		||||
end subroutine multimode_decoder
 | 
			
		||||
 | 
			
		||||
@ -1,4 +1,4 @@
 | 
			
		||||
subroutine ft8b(datetime,s,candidate,ncand)
 | 
			
		||||
subroutine ft8b(s,f1,xdt,nharderrors,dmin,nbadcrc,message)
 | 
			
		||||
 | 
			
		||||
  include 'ft8_params.f90'
 | 
			
		||||
  parameter(NRECENT=10)
 | 
			
		||||
@ -16,74 +16,65 @@ subroutine ft8b(datetime,s,candidate,ncand)
 | 
			
		||||
  tstep=0.5*NSPS/12000.0
 | 
			
		||||
  df=12000.0/NFFT1
 | 
			
		||||
 | 
			
		||||
  do icand=1,ncand
 | 
			
		||||
     f1=candidate(1,icand)
 | 
			
		||||
     xdt=candidate(2,icand)
 | 
			
		||||
     sync=candidate(3,icand)
 | 
			
		||||
     i0=nint(f1/df)
 | 
			
		||||
     j0=nint(xdt/tstep)
 | 
			
		||||
  i0=nint(f1/df)
 | 
			
		||||
  j0=nint(xdt/tstep)
 | 
			
		||||
 | 
			
		||||
     j=0
 | 
			
		||||
     ia=i0
 | 
			
		||||
     ib=i0+14
 | 
			
		||||
     do k=1,NN
 | 
			
		||||
        if(k.le.7) cycle
 | 
			
		||||
        if(k.ge.37 .and. k.le.43) cycle
 | 
			
		||||
        if(k.gt.72) cycle
 | 
			
		||||
        n=j0+2*(k-1)+1
 | 
			
		||||
        if(n.lt.1) cycle
 | 
			
		||||
        j=j+1
 | 
			
		||||
        s1(0:7,j)=s(ia:ib:2,n)
 | 
			
		||||
     enddo
 | 
			
		||||
     do j=1,ND
 | 
			
		||||
        ps=s1(0:7,j)
 | 
			
		||||
        where (ps.gt.0.0) ps=log(ps)
 | 
			
		||||
        r1=max(ps(1),ps(3),ps(5),ps(7))-max(ps(0),ps(2),ps(4),ps(6))
 | 
			
		||||
        r2=max(ps(2),ps(3),ps(6),ps(7))-max(ps(0),ps(1),ps(4),ps(5))
 | 
			
		||||
        r4=max(ps(4),ps(5),ps(6),ps(7))-max(ps(0),ps(1),ps(2),ps(3))
 | 
			
		||||
        rxdata(3*j-2)=r4
 | 
			
		||||
        rxdata(3*j-1)=r2
 | 
			
		||||
        rxdata(3*j)=r1
 | 
			
		||||
     enddo
 | 
			
		||||
  j=0
 | 
			
		||||
  ia=i0
 | 
			
		||||
  ib=i0+14
 | 
			
		||||
  do k=1,NN
 | 
			
		||||
     if(k.le.7) cycle
 | 
			
		||||
     if(k.ge.37 .and. k.le.43) cycle
 | 
			
		||||
     if(k.gt.72) cycle
 | 
			
		||||
     n=j0+2*(k-1)+1
 | 
			
		||||
     if(n.lt.1) cycle
 | 
			
		||||
     j=j+1
 | 
			
		||||
     s1(0:7,j)=s(ia:ib:2,n)
 | 
			
		||||
  enddo
 | 
			
		||||
  do j=1,ND
 | 
			
		||||
     ps=s1(0:7,j)
 | 
			
		||||
     where (ps.gt.0.0) ps=log(ps)
 | 
			
		||||
     r1=max(ps(1),ps(3),ps(5),ps(7))-max(ps(0),ps(2),ps(4),ps(6))
 | 
			
		||||
     r2=max(ps(2),ps(3),ps(6),ps(7))-max(ps(0),ps(1),ps(4),ps(5))
 | 
			
		||||
     r4=max(ps(4),ps(5),ps(6),ps(7))-max(ps(0),ps(1),ps(2),ps(3))
 | 
			
		||||
     rxdata(3*j-2)=r4
 | 
			
		||||
     rxdata(3*j-1)=r2
 | 
			
		||||
     rxdata(3*j)=r1
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
     rxav=sum(rxdata)/(3.0*ND)
 | 
			
		||||
     rx2av=sum(rxdata*rxdata)/(3.0*ND)
 | 
			
		||||
     var=rx2av-rxav*rxav
 | 
			
		||||
     if( var .gt. 0.0 ) then
 | 
			
		||||
       rxsig=sqrt(var)
 | 
			
		||||
     else
 | 
			
		||||
       rxsig=sqrt(rx2av)
 | 
			
		||||
     endif
 | 
			
		||||
     rxdata=rxdata/rxsig
 | 
			
		||||
     ss=0.84
 | 
			
		||||
     llr=2.0*rxdata/(ss*ss)
 | 
			
		||||
     apmask=0
 | 
			
		||||
     cw=0
 | 
			
		||||
  rxav=sum(rxdata)/(3.0*ND)
 | 
			
		||||
  rx2av=sum(rxdata*rxdata)/(3.0*ND)
 | 
			
		||||
  var=rx2av-rxav*rxav
 | 
			
		||||
  if( var .gt. 0.0 ) then
 | 
			
		||||
     rxsig=sqrt(var)
 | 
			
		||||
  else
 | 
			
		||||
     rxsig=sqrt(rx2av)
 | 
			
		||||
  endif
 | 
			
		||||
  rxdata=rxdata/rxsig
 | 
			
		||||
  ss=0.84
 | 
			
		||||
  llr=2.0*rxdata/(ss*ss)
 | 
			
		||||
  apmask=0
 | 
			
		||||
  cw=0
 | 
			
		||||
! cw will be needed for subtraction.
 | 
			
		||||
! dmin is the correlation discrepancy of a returned codeword - it is 
 | 
			
		||||
!      used to select the best codeword within osd174.
 | 
			
		||||
     call bpdecode174(llr,apmask,max_iterations,decoded,cw,nharderrors)
 | 
			
		||||
     dmin=0.0
 | 
			
		||||
     if(nharderrors.lt.0) then
 | 
			
		||||
       call osd174(llr,norder,decoded,cw,nharderrors,dmin)
 | 
			
		||||
  call bpdecode174(llr,apmask,max_iterations,decoded,cw,nharderrors)
 | 
			
		||||
  dmin=0.0
 | 
			
		||||
  if(nharderrors.lt.0) then
 | 
			
		||||
     call osd174(llr,norder,decoded,cw,nharderrors,dmin)
 | 
			
		||||
! This threshold needs to be tuned. 99.0 should pass everything.
 | 
			
		||||
       if( dmin .gt. 99.0 ) nharderrors=-1
 | 
			
		||||
     endif
 | 
			
		||||
! Reject the all-zero codeword
 | 
			
		||||
     if( count(cw.eq.0) .eq. 174 ) cycle
 | 
			
		||||
     nbadcrc=1
 | 
			
		||||
     if( nharderrors .ge. 0 ) call chkcrc12a(decoded,nbadcrc)
 | 
			
		||||
     message='                      '
 | 
			
		||||
     if(nbadcrc.eq.0) then
 | 
			
		||||
        call extractmessage174(decoded,message,ncrcflag,recent_calls,nrecent)
 | 
			
		||||
        nsnr=nint(10.0*log10(sync) - 25.5)    !### empirical ###
 | 
			
		||||
        write(*,1112) datetime(8:13),nsnr,xdt,nint(f1),message
 | 
			
		||||
1112    format(a6,i4,f5.1,i5," ~ ",a22)
 | 
			
		||||
     endif
 | 
			
		||||
     write(13,1110) datetime,0,nsnr,xdt,f1,xdta,f1a,    &
 | 
			
		||||
          nharderrors,dmin,message
 | 
			
		||||
1110 format(a13,2i4,2(f6.2,f7.1),i4,' ~ ',f6.2,2x,a22)
 | 
			
		||||
  enddo
 | 
			
		||||
     if( dmin .gt. 99.0 ) nharderrors=-1
 | 
			
		||||
  endif
 | 
			
		||||
  nbadcrc=1
 | 
			
		||||
  message='                      '
 | 
			
		||||
  if(count(cw.eq.0).eq.174) go to 900           !Reject the all-zero codeword
 | 
			
		||||
  if(nharderrors.ge.0) call chkcrc12a(decoded,nbadcrc)
 | 
			
		||||
  if(nbadcrc.eq.0) then
 | 
			
		||||
     call extractmessage174(decoded,message,ncrcflag,recent_calls,nrecent)
 | 
			
		||||
!     write(*,1112) datetime(8:13),nsnr,xdt,nint(f1),message
 | 
			
		||||
!1112 format(a6,i4,f5.1,i5," ~ ",a22)
 | 
			
		||||
  endif
 | 
			
		||||
900 continue
 | 
			
		||||
 | 
			
		||||
  return
 | 
			
		||||
end subroutine ft8b
 | 
			
		||||
 | 
			
		||||
@ -7,8 +7,7 @@ module ft8_decode
 | 
			
		||||
  end type ft8_decoder
 | 
			
		||||
 | 
			
		||||
  abstract interface
 | 
			
		||||
     subroutine ft8_decode_callback (this, sync, snr, dt, freq, drift, &
 | 
			
		||||
          decoded)
 | 
			
		||||
     subroutine ft8_decode_callback (this,sync,snr,dt,freq,nbadcrc,decoded)
 | 
			
		||||
       import ft8_decoder
 | 
			
		||||
       implicit none
 | 
			
		||||
       class(ft8_decoder), intent(inout) :: this
 | 
			
		||||
@ -16,7 +15,7 @@ module ft8_decode
 | 
			
		||||
       integer, intent(in) :: snr
 | 
			
		||||
       real, intent(in) :: dt
 | 
			
		||||
       real, intent(in) :: freq
 | 
			
		||||
       integer, intent(in) :: drift
 | 
			
		||||
       integer, intent(in) :: nbadcrc
 | 
			
		||||
       character(len=22), intent(in) :: decoded
 | 
			
		||||
     end subroutine ft8_decode_callback
 | 
			
		||||
  end interface
 | 
			
		||||
@ -25,9 +24,8 @@ contains
 | 
			
		||||
 | 
			
		||||
  subroutine decode(this,callback,ss,iwave,nfqso,newdat,npts8,nutc,nfa,    &
 | 
			
		||||
       nfsplit,nfb,ntol,nzhsym,nagain,ndepth,nmode,nsubmode,nexp_decode)
 | 
			
		||||
    use timer_module, only: timer
 | 
			
		||||
 | 
			
		||||
!    include 'constants.f90'
 | 
			
		||||
    use timer_module, only: timer
 | 
			
		||||
    include 'fsk4hf/ft8_params.f90'
 | 
			
		||||
 | 
			
		||||
    class(ft8_decoder), intent(inout) :: this
 | 
			
		||||
@ -37,17 +35,35 @@ contains
 | 
			
		||||
    real candidate(3,100)
 | 
			
		||||
    logical, intent(in) :: newdat, nagain
 | 
			
		||||
    integer*2 iwave(15*12000)
 | 
			
		||||
    character*13 datetime
 | 
			
		||||
    character datetime*13,message*22
 | 
			
		||||
 | 
			
		||||
    this%callback => callback
 | 
			
		||||
 | 
			
		||||
    write(datetime,1001) nutc        !### TEMPORARY ###
 | 
			
		||||
1001 format("000000_",i6.6)
 | 
			
		||||
 | 
			
		||||
    call timer('sync8   ',0)
 | 
			
		||||
    call sync8(iwave,s,candidate,ncand)
 | 
			
		||||
    call ft8b(datetime,s,candidate,ncand)
 | 
			
		||||
!     if (associated(this%callback)) then
 | 
			
		||||
!        call this%callback(sync,nsnr,xdt,freq,ndrift,msg)
 | 
			
		||||
!     end if
 | 
			
		||||
     
 | 
			
		||||
    call timer('sync8   ',1)
 | 
			
		||||
 | 
			
		||||
    rewind 51
 | 
			
		||||
    do icand=1,ncand
 | 
			
		||||
       f1=candidate(1,icand)
 | 
			
		||||
       xdt=candidate(2,icand)
 | 
			
		||||
       sync=candidate(3,icand)
 | 
			
		||||
       nsnr=min(99,nint(10.0*log10(sync) - 25.5))    !### empirical ###
 | 
			
		||||
       call timer('ft8b    ',0)
 | 
			
		||||
       call ft8b(s,f1,xdt,nharderrors,dmin,nbadcrc,message)
 | 
			
		||||
       call timer('ft8b    ',1)
 | 
			
		||||
       if (associated(this%callback)) call this%callback(sync,nsnr,xdt,   &
 | 
			
		||||
            freq,nbadcrc,message)
 | 
			
		||||
!       write(13,1110) datetime,0,nsnr,xdt,f1,nharderrors,dmin,message
 | 
			
		||||
!1110   format(a13,2i4,f6.2,f7.1,i4,' ~ ',f6.2,2x,a22,'  FT8')
 | 
			
		||||
       write(51,3051) xdt,f1,sync,dmin,nsnr,nharderrors,nbadcrc,message
 | 
			
		||||
3051 format(4f9.1,3i5,2x,a22)
 | 
			
		||||
    enddo
 | 
			
		||||
    flush(51)
 | 
			
		||||
 | 
			
		||||
    return
 | 
			
		||||
  end subroutine decode
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user