mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-11-03 13:30:52 -05:00 
			
		
		
		
	More work toward testing Q65-style sync.
This commit is contained in:
		
							parent
							
								
									4491da67f7
								
							
						
					
					
						commit
						6d4372cafe
					
				@ -13,14 +13,15 @@ subroutine sfox_gen(idat,f0,fsample,isync,cdat)
 | 
				
			|||||||
  j=1
 | 
					  j=1
 | 
				
			||||||
  k=0
 | 
					  k=0
 | 
				
			||||||
  do i=1,NDS
 | 
					  do i=1,NDS
 | 
				
			||||||
     if(j.le.NS .and. i.eq.isync(min(j,NS))) then
 | 
					     if(j.le.NS .and. i.eq.isync(j)) then
 | 
				
			||||||
        j=j+1                   !Index for next sync symbol
 | 
					        if(j.lt.NS) j=j+1       !Index for next sync symbol
 | 
				
			||||||
        itone(i)=0              !Insert sync symbol at tone 0
 | 
					        itone(i)=0              !Insert sync symbol at tone 0
 | 
				
			||||||
     else
 | 
					     else
 | 
				
			||||||
        k=k+1
 | 
					        k=k+1
 | 
				
			||||||
        itone(i)=idat(k) + 1    !Symbol value 0 is transmitted at tone 1, etc.
 | 
					        itone(i)=idat(k) + 1    !Symbol value 0 is transmitted at tone 1, etc.
 | 
				
			||||||
     endif
 | 
					     endif
 | 
				
			||||||
  enddo
 | 
					  enddo
 | 
				
			||||||
 | 
					!  print*,'aaa',NN,k,NS,isync(NS),NDS
 | 
				
			||||||
  
 | 
					  
 | 
				
			||||||
  df=fsample/NSPS
 | 
					  df=fsample/NSPS
 | 
				
			||||||
  w=1.0
 | 
					  w=1.0
 | 
				
			||||||
 | 
				
			|||||||
@ -1,7 +1,8 @@
 | 
				
			|||||||
module sfox_mod
 | 
					module sfox_mod
 | 
				
			||||||
  
 | 
					  
 | 
				
			||||||
  parameter (NMAX=15*12000)       !Samples in iwave (180,000)
 | 
					  parameter (NMAX=15*12000)       !Samples in iwave (180,000)
 | 
				
			||||||
  integer MM,NQ,NN,KK,NS,NDS,NFZ,NSPS,NSYNC,NZ,NFFT,NFFT1
 | 
					  integer MM,NQ,NN,KK,NS,NDS,NFZ,NSPS,NSYNC,NZ,NFFT1
 | 
				
			||||||
 | 
					  real baud,tsym,bw
 | 
				
			||||||
 | 
					
 | 
				
			||||||
contains
 | 
					contains
 | 
				
			||||||
  subroutine sfox_init(mm0,nn0,kk0,itu,fspread,delay,fsample,ns0)
 | 
					  subroutine sfox_init(mm0,nn0,kk0,itu,fspread,delay,fsample,ns0)
 | 
				
			||||||
@ -29,9 +30,12 @@ contains
 | 
				
			|||||||
    NSPS=isps(iloc(1))  !Samples per symbol
 | 
					    NSPS=isps(iloc(1))  !Samples per symbol
 | 
				
			||||||
    NSYNC=NS*NSPS       !Samples in sync waveform
 | 
					    NSYNC=NS*NSPS       !Samples in sync waveform
 | 
				
			||||||
    NZ=NSPS*NDS         !Samples in full Tx waveform
 | 
					    NZ=NSPS*NDS         !Samples in full Tx waveform
 | 
				
			||||||
    NFFT=32768          !Length of FFT for sync waveform
 | 
					 | 
				
			||||||
    NFFT1=2*NSPS        !Length of FFTs for symbol spectra
 | 
					    NFFT1=2*NSPS        !Length of FFTs for symbol spectra
 | 
				
			||||||
    
 | 
					    
 | 
				
			||||||
 | 
					    baud=fsample/NSPS
 | 
				
			||||||
 | 
					    tsym=1.0/baud
 | 
				
			||||||
 | 
					    bw=NQ*baud
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    fspread=0.0
 | 
					    fspread=0.0
 | 
				
			||||||
    delay=0.0
 | 
					    delay=0.0
 | 
				
			||||||
    if(itu.eq.'LQ') then
 | 
					    if(itu.eq.'LQ') then
 | 
				
			||||||
 | 
				
			|||||||
@ -1,38 +1,111 @@
 | 
				
			|||||||
subroutine sfox_sync(crcvd,fsample,isync,f,t)
 | 
					subroutine sfox_sync(iwave,fsample,isync,f,t)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  use sfox_mod
 | 
					  use sfox_mod
 | 
				
			||||||
  parameter (NSTEPS=8)
 | 
					  parameter (NSTEPS=8)
 | 
				
			||||||
  complex crcvd(NMAX)                      !Signal as received
 | 
					  integer*2 iwave(NMAX)
 | 
				
			||||||
 | 
					  integer isync(44)
 | 
				
			||||||
 | 
					  integer ipeak(1)
 | 
				
			||||||
  complex, allocatable :: c(:)             !Work array
 | 
					  complex, allocatable :: c(:)             !Work array
 | 
				
			||||||
  integer isync(50)
 | 
					  real x(171)
 | 
				
			||||||
  real, allocatable :: s(:,:)              !Symbol spectra, 1/8 symbol steps
 | 
					  real, allocatable :: s(:,:)              !Symbol spectra, stepped by NSTEPS 
 | 
				
			||||||
 | 
					  real, allocatable :: savg(:)             !Average spectrum
 | 
				
			||||||
  real, allocatable :: ccf(:,:)            !
 | 
					  real, allocatable :: ccf(:,:)            !
 | 
				
			||||||
!  character*1 line(-30:30),mark(0:6)
 | 
					  character*1 line(-15:15),mark(0:6),c1
 | 
				
			||||||
!  data mark/' ','.','-','+','X','$','#'/
 | 
					  data mark/' ','.','-','+','X','$','#'/
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  nh=NFFT1/2                               !1024
 | 
					  nh=NFFT1/2
 | 
				
			||||||
  istep=nh/NSTEPS                          !128
 | 
					  istep=NSPS/NSTEPS
 | 
				
			||||||
  nsz=(nint(3.0*fsample) + NS*NSPS)/istep  !473
 | 
					  jz=(13.5*fsample)/istep
 | 
				
			||||||
  df=fsample/NFFT1                         !5.86 Hz
 | 
					  df=fsample/NFFT1
 | 
				
			||||||
  tstep=istep/fsample                      !0.0107 s
 | 
					  tstep=istep/fsample
 | 
				
			||||||
 | 
					  x=0.
 | 
				
			||||||
 | 
					  do i=1,NS
 | 
				
			||||||
 | 
					     x(isync(i))=1.0
 | 
				
			||||||
 | 
					  enddo
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  allocate(c(0:nfft1-1))
 | 
					  allocate(s(0:nh/2,jz))
 | 
				
			||||||
  allocate(s(nh/2,nsz))
 | 
					  allocate(savg(0:nh/2))
 | 
				
			||||||
 | 
					  allocate(c(0:NFFT1-1))
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! Compute symbol spectra with df=baud/2 and NSTEPS steps per symbol.
 | 
					  s=0.
 | 
				
			||||||
  ia=1-istep
 | 
					  savg=0.
 | 
				
			||||||
  fac=1.0/NFFT1
 | 
					  fac=1.0/NFFT1
 | 
				
			||||||
  do j=1,nsz
 | 
					! Compute symbol spectra with df=baud/2 and NSTEPS steps per symbol.
 | 
				
			||||||
     ia=ia+istep
 | 
					  do j=1,jz
 | 
				
			||||||
     ib=ia+nh-1
 | 
					     k=(j-1)*istep
 | 
				
			||||||
     c(0:NSPS-1)=fac*crcvd(ia:ib)
 | 
					     do i=0,nh-1
 | 
				
			||||||
     c(NSPS:)=0.
 | 
					        c(i)=cmplx(fac*iwave(k+2*i+1),fac*iwave(k+2*i+2))
 | 
				
			||||||
     call four2a(c,NFFT1,1,-1,1)
 | 
					     enddo
 | 
				
			||||||
     do i=1,nh/2
 | 
					     c(nh:)=0.
 | 
				
			||||||
        s(i,j)=real(c(i))**2 + aimag(c(i))**2
 | 
					     call four2a(c,NFFT1,1,-1,0)           !Forward FFT, r2c
 | 
				
			||||||
 | 
					     do i=0,nh/2
 | 
				
			||||||
 | 
					        p=real(c(i))*real(c(i)) + aimag(c(i))*aimag(c(i))
 | 
				
			||||||
 | 
					        s(i,j)=p
 | 
				
			||||||
 | 
					        savg(i)=savg(i) + p
 | 
				
			||||||
     enddo
 | 
					     enddo
 | 
				
			||||||
  enddo
 | 
					  enddo
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  pmax=maxval(s(82:112,1:jz))
 | 
				
			||||||
 | 
					  s=s/pmax
 | 
				
			||||||
 | 
					  do j=jz,1,-1
 | 
				
			||||||
 | 
					     do i=-15,15
 | 
				
			||||||
 | 
					        k=6.001*s(97+i,j)
 | 
				
			||||||
 | 
					        line(i)=mark(k)
 | 
				
			||||||
 | 
					     enddo
 | 
				
			||||||
 | 
					     c1=' '
 | 
				
			||||||
 | 
					     k=j/NSTEPS + 1
 | 
				
			||||||
 | 
					     if(k.le.171) then
 | 
				
			||||||
 | 
					        if(x(k).ne.0.0) c1='*'
 | 
				
			||||||
 | 
					     endif
 | 
				
			||||||
 | 
					!     write(*,2001) j,c1,line
 | 
				
			||||||
 | 
					!2001 format(i3,2x,a1,' |',31a1,'|')
 | 
				
			||||||
 | 
					     xx=0
 | 
				
			||||||
 | 
					     if(c1.eq.'*') xx=1
 | 
				
			||||||
 | 
					     write(44,3044) j*tstep,xx,3.5*s(96:98,j)
 | 
				
			||||||
 | 
					3044 format(f10.4,4f10.4)
 | 
				
			||||||
 | 
					  enddo
 | 
				
			||||||
 | 
					     
 | 
				
			||||||
 | 
					  savg=savg/jz
 | 
				
			||||||
 | 
					  ipeak=maxloc(savg(82:112))
 | 
				
			||||||
 | 
					  i0=ipeak(1)+81
 | 
				
			||||||
 | 
					  dxi=0.
 | 
				
			||||||
 | 
					!  if(i0.gt.0 .and. i0.lt.nh/2) then
 | 
				
			||||||
 | 
					!     call peakup(savg(i0-1),savg(i0),savg(i0+1),dxi)
 | 
				
			||||||
 | 
					!  endif
 | 
				
			||||||
 | 
					  f=(i0+dxi)*df + bw/2.0
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  do j=1,jz
 | 
				
			||||||
 | 
					     k=j/NSTEPS + 1
 | 
				
			||||||
 | 
					     xx=0
 | 
				
			||||||
 | 
					     if(k.le.171) xx=x(k)
 | 
				
			||||||
 | 
					     write(43,3043) j,s(i0,j),xx
 | 
				
			||||||
 | 
					3043 format(i5,2f12.3)
 | 
				
			||||||
 | 
					  enddo
 | 
				
			||||||
 | 
					  lagmax=1.0/tstep + 1
 | 
				
			||||||
 | 
					  pmax=0.
 | 
				
			||||||
 | 
					  lagpk=-99
 | 
				
			||||||
 | 
					!  print*,i0,jz,tstep,lagmax
 | 
				
			||||||
 | 
					  do lag=0,lagmax
 | 
				
			||||||
 | 
					     p=0.
 | 
				
			||||||
 | 
					     do i=1,NS
 | 
				
			||||||
 | 
					        k=NSTEPS*(isync(i)-1) + 1 + lag
 | 
				
			||||||
 | 
					        p=p + s(i0,k)
 | 
				
			||||||
 | 
					     enddo
 | 
				
			||||||
 | 
					     p=p/NS
 | 
				
			||||||
 | 
					     if(p.gt.pmax) then
 | 
				
			||||||
 | 
					        pmax=p
 | 
				
			||||||
 | 
					        lagpk=lag
 | 
				
			||||||
 | 
					     endif
 | 
				
			||||||
 | 
					     write(42,3042) lag,lag*tstep,p
 | 
				
			||||||
 | 
					3042 format(i5,2f15.3)
 | 
				
			||||||
 | 
					  enddo
 | 
				
			||||||
 | 
					  t=lagpk*tstep
 | 
				
			||||||
 | 
					!  print*,f,t
 | 
				
			||||||
 | 
					  if(NS.ne.-99) return
 | 
				
			||||||
 | 
					  
 | 
				
			||||||
 | 
					  nsz=(nint(3.0*fsample) + NS*NSPS)/istep
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  pmax=0.
 | 
					  pmax=0.
 | 
				
			||||||
  ntol=100
 | 
					  ntol=100
 | 
				
			||||||
  iz=nint(ntol/df)
 | 
					  iz=nint(ntol/df)
 | 
				
			||||||
 | 
				
			|||||||
@ -37,8 +37,6 @@ program sfoxtest
 | 
				
			|||||||
            116, 122, 130, 131, 134, 136, 137, 140, 146, 154,  &
 | 
					            116, 122, 130, 131, 134, 136, 137, 140, 146, 154,  &
 | 
				
			||||||
            159, 161, 163, 165/
 | 
					            159, 161, 163, 165/
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
  nargs=iargc()
 | 
					  nargs=iargc()
 | 
				
			||||||
  if(nargs.ne.11) then
 | 
					  if(nargs.ne.11) then
 | 
				
			||||||
     print*,'Usage:   sfoxtest  f0   DT  ITU M  N   K NS v hs nfiles snr'
 | 
					     print*,'Usage:   sfoxtest  f0   DT  ITU M  N   K NS v hs nfiles snr'
 | 
				
			||||||
@ -81,16 +79,12 @@ program sfoxtest
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
  fsample=12000.0                   !Sample rate (Hz)
 | 
					  fsample=12000.0                   !Sample rate (Hz)
 | 
				
			||||||
  call sfox_init(mm0,nn0,kk0,itu,fspread,delay,fsample,ns0)
 | 
					  call sfox_init(mm0,nn0,kk0,itu,fspread,delay,fsample,ns0)
 | 
				
			||||||
  baud=fsample/NSPS
 | 
					 | 
				
			||||||
  tsym=1.0/baud
 | 
					 | 
				
			||||||
  bw=NQ*baud
 | 
					 | 
				
			||||||
  maxerr=(NN-KK)/2
 | 
					 | 
				
			||||||
  tsync=NSYNC/fsample
 | 
					  tsync=NSYNC/fsample
 | 
				
			||||||
  txt=(NN+NS)*NSPS/fsample
 | 
					  txt=(NN+NS)*NSPS/fsample
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  write(*,1000) MM,NN,KK,NSPS,baud,bw,itu,tsync,txt
 | 
					  write(*,1000) MM,NN,KK,NSPS,baud,bw,itu,tsync,txt
 | 
				
			||||||
1000 format('M:',i2,'   Base code: (',i3,',',i3,')   NSPS:',i5,   &
 | 
					1000 format('M:',i2,'   Base code: (',i3,',',i3,')   NSPS:',i5,   &
 | 
				
			||||||
          '   Baud:',f7.3,'   BW:',f6.0/                   &
 | 
					          '   Baud:',f7.3,'   BW:',f9.3/                   &
 | 
				
			||||||
          'Channel: ',a2,'   Tsync:',f4.1,'   TxT:',f5.1/)
 | 
					          'Channel: ',a2,'   Tsync:',f4.1,'   TxT:',f5.1/)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! Allocate storage for arrays that depend on code parameters.
 | 
					! Allocate storage for arrays that depend on code parameters.
 | 
				
			||||||
@ -170,7 +164,8 @@ program sfoxtest
 | 
				
			|||||||
        call timer('watterso',1)
 | 
					        call timer('watterso',1)
 | 
				
			||||||
        crcvd=sig*crcvd+cnoise
 | 
					        crcvd=sig*crcvd+cnoise
 | 
				
			||||||
 | 
					
 | 
				
			||||||
        dat=aimag(sigr*cdat(1:NMAX)) + xnoise     !Add generated AWGN noise
 | 
					!        dat=aimag(sigr*cdat(1:NMAX)) + xnoise     !Add generated AWGN noise
 | 
				
			||||||
 | 
					        dat=aimag(sigr*crcvd(1:NMAX)) + xnoise     !Add generated AWGN noise
 | 
				
			||||||
        fac=32767.0
 | 
					        fac=32767.0
 | 
				
			||||||
        if(snr.ge.90.0) iwave(1:NMAX)=nint(fac*dat(1:NMAX))
 | 
					        if(snr.ge.90.0) iwave(1:NMAX)=nint(fac*dat(1:NMAX))
 | 
				
			||||||
        if(snr.lt.90.0) iwave(1:NMAX)=nint(rms*dat(1:NMAX))
 | 
					        if(snr.lt.90.0) iwave(1:NMAX)=nint(rms*dat(1:NMAX))
 | 
				
			||||||
@ -181,12 +176,13 @@ program sfoxtest
 | 
				
			|||||||
        else
 | 
					        else
 | 
				
			||||||
! Find signal freq and DT
 | 
					! Find signal freq and DT
 | 
				
			||||||
           call timer('sync    ',0)
 | 
					           call timer('sync    ',0)
 | 
				
			||||||
           call sfox_sync(crcvd,fsample,isync,f,t)
 | 
					           call sfox_sync(iwave,fsample,isync,f,t)
 | 
				
			||||||
           call timer('sync    ',1)
 | 
					           call timer('sync    ',1)
 | 
				
			||||||
        endif
 | 
					        endif
 | 
				
			||||||
 | 
					 | 
				
			||||||
        ferr=f-f1
 | 
					        ferr=f-f1
 | 
				
			||||||
        terr=t-xdt
 | 
					        terr=t-xdt
 | 
				
			||||||
 | 
					!        write(*,4100) f1,f,ferr,xdt,t,terr
 | 
				
			||||||
 | 
					!4100    format(3f10.1,3f10.3)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
        igoodsync=0
 | 
					        igoodsync=0
 | 
				
			||||||
        if(abs(ferr).lt.baud/2.0 .and. abs(terr).lt.tsym/4.0) then
 | 
					        if(abs(ferr).lt.baud/2.0 .and. abs(terr).lt.tsym/4.0) then
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user