mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-11-03 13:30:52 -05:00 
			
		
		
		
	Further code cleanup.
git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@3199 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
		
							parent
							
								
									695ce7b83e
								
							
						
					
					
						commit
						e6102f9ef2
					
				@ -27,7 +27,7 @@ OBJS1 = pctile.o graycode.o sort.o ssort.o \
 | 
				
			|||||||
	packbits.o unpackbits.o encode232.o interleave9.o \
 | 
						packbits.o unpackbits.o encode232.o interleave9.o \
 | 
				
			||||||
	entail.o fano232.o gran.o sync9.o decode9.o \
 | 
						entail.o fano232.o gran.o sync9.o decode9.o \
 | 
				
			||||||
	fil3.o redsync.o decoder.o grid2n.o n2grid.o timer.o \
 | 
						fil3.o redsync.o decoder.o grid2n.o n2grid.o timer.o \
 | 
				
			||||||
	decode9a.o peakdt9.o getlags.o afc9.o fchisq.o \
 | 
						softsym.o peakdt9.o getlags.o afc9.o fchisq.o \
 | 
				
			||||||
	twkfreq.o downsam9.o symspec2.o ipcomm.o sleep_msec.o \
 | 
						twkfreq.o downsam9.o symspec2.o ipcomm.o sleep_msec.o \
 | 
				
			||||||
	stdmsg.o sec_midn.o cutil.o azdist.o geodist.o morse.o \
 | 
						stdmsg.o sec_midn.o cutil.o azdist.o geodist.o morse.o \
 | 
				
			||||||
	fillcom.o
 | 
						fillcom.o
 | 
				
			||||||
 | 
				
			|||||||
@ -53,9 +53,7 @@ subroutine decoder(ss,c0,nstandalone)
 | 
				
			|||||||
  endif
 | 
					  endif
 | 
				
			||||||
  if(nsps.eq.0) stop 'Error: bad TRperiod'    !Better: return an error code###
 | 
					  if(nsps.eq.0) stop 'Error: bad TRperiod'    !Better: return an error code###
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  kstep=nsps/2
 | 
					  tstep=0.5*nsps/12000.0                      !Half-symbol step (seconds)
 | 
				
			||||||
  tstep=kstep/12000.0
 | 
					 | 
				
			||||||
!  tstep=0.5*tstep
 | 
					 | 
				
			||||||
  idf=ntol/df3 + 0.999
 | 
					  idf=ntol/df3 + 0.999
 | 
				
			||||||
  done=.false.
 | 
					  done=.false.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -86,6 +84,7 @@ subroutine decoder(ss,c0,nstandalone)
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
     ccfok=.false.
 | 
					     ccfok=.false.
 | 
				
			||||||
     ccfok(max(ipk-idf,1):min(ipk+idf,NSMAX))=.true.
 | 
					     ccfok(max(ipk-idf,1):min(ipk+idf,NSMAX))=.true.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
     if(nqd.eq.1) then
 | 
					     if(nqd.eq.1) then
 | 
				
			||||||
        ia1=ia
 | 
					        ia1=ia
 | 
				
			||||||
        ib1=ib
 | 
					        ib1=ib
 | 
				
			||||||
@ -113,12 +112,12 @@ subroutine decoder(ss,c0,nstandalone)
 | 
				
			|||||||
             (ccfred(i).lt.ccfred(i+1))) cycle
 | 
					             (ccfred(i).lt.ccfred(i+1))) cycle
 | 
				
			||||||
        if(nqd.eq.1 .or.                                                   &
 | 
					        if(nqd.eq.1 .or.                                                   &
 | 
				
			||||||
           (ccfred(i).ge.ccflim .and. abs(f-fgood).gt.10.0*df8)) then
 | 
					           (ccfred(i).ge.ccflim .and. abs(f-fgood).gt.10.0*df8)) then
 | 
				
			||||||
           call timer('decode9a',0)
 | 
					           call timer('softsym ',0)
 | 
				
			||||||
           fpk=1000.0 + df3*(i-1)
 | 
					           fpk=1000.0 + df3*(i-1)
 | 
				
			||||||
           c1(1:npts8)=conjg(c0(1:npts8))
 | 
					           c1(1:npts8)=conjg(c0(1:npts8))
 | 
				
			||||||
           call decode9a(c1,npts8,nsps8,fpk,syncpk,snrdb,xdt,freq,drift,   &
 | 
					           call softsym(c1,npts8,nsps8,fpk,syncpk,snrdb,xdt,freq,drift,   &
 | 
				
			||||||
                i1SoftSymbols)
 | 
					                i1SoftSymbols)
 | 
				
			||||||
           call timer('decode9a',1)
 | 
					           call timer('softsym ',1)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
           call timer('decode9 ',0)
 | 
					           call timer('decode9 ',0)
 | 
				
			||||||
           call decode9(i1SoftSymbols,limit,nlim,msg)
 | 
					           call decode9(i1SoftSymbols,limit,nlim,msg)
 | 
				
			||||||
 | 
				
			|||||||
@ -3,8 +3,6 @@ program jt9
 | 
				
			|||||||
! Decoder for JT9.  Can run stand-alone, reading data from *.wav files;
 | 
					! Decoder for JT9.  Can run stand-alone, reading data from *.wav files;
 | 
				
			||||||
! or as the back end of wsjt-x, with data placed in a shared memory region.
 | 
					! or as the back end of wsjt-x, with data placed in a shared memory region.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! NB: For unknown reason, ***MUST*** be compiled by g95 with -O0 !!!
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
  character*80 arg,infile
 | 
					  character*80 arg,infile
 | 
				
			||||||
  parameter (NMAX=1800*12000)        !Total sample intervals per 30 minutes
 | 
					  parameter (NMAX=1800*12000)        !Total sample intervals per 30 minutes
 | 
				
			||||||
  parameter (NDMAX=1800*1500)        !Sample intervals at 1500 Hz rate
 | 
					  parameter (NDMAX=1800*1500)        !Sample intervals at 1500 Hz rate
 | 
				
			||||||
@ -31,20 +29,17 @@ program jt9
 | 
				
			|||||||
  call getarg(1,arg)
 | 
					  call getarg(1,arg)
 | 
				
			||||||
  if(arg(1:2).eq.'-s') then
 | 
					  if(arg(1:2).eq.'-s') then
 | 
				
			||||||
     call jt9a
 | 
					     call jt9a
 | 
				
			||||||
!    call ftnquit
 | 
					 | 
				
			||||||
     go to 999
 | 
					     go to 999
 | 
				
			||||||
  endif
 | 
					  endif
 | 
				
			||||||
  read(arg,*) ntrperiod
 | 
					  read(arg,*) ntrperiod
 | 
				
			||||||
  call getarg(2,arg)
 | 
					  call getarg(2,arg)
 | 
				
			||||||
  read(arg,*) ndepth
 | 
					  read(arg,*) ndepth
 | 
				
			||||||
 | 
					 | 
				
			||||||
  ifile1=3
 | 
					  ifile1=3
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  limtrace=0
 | 
					  limtrace=0
 | 
				
			||||||
  lu=12
 | 
					  lu=12
 | 
				
			||||||
  nfa=1000
 | 
					  nfa=1000
 | 
				
			||||||
  nfb=2000
 | 
					  nfb=2000
 | 
				
			||||||
  ntol=500
 | 
					 | 
				
			||||||
  mousefqso=1500
 | 
					  mousefqso=1500
 | 
				
			||||||
  newdat=1
 | 
					  newdat=1
 | 
				
			||||||
  nb=0
 | 
					  nb=0
 | 
				
			||||||
 | 
				
			|||||||
@ -1,7 +1,6 @@
 | 
				
			|||||||
subroutine jt9a
 | 
					subroutine jt9a
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! NB: this interface block is required by g95, but must be omitted
 | 
					! These routines connect the shared memory region to the decoder.
 | 
				
			||||||
!     for gfortran.  (????)
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
  interface
 | 
					  interface
 | 
				
			||||||
     function address_jt9()
 | 
					     function address_jt9()
 | 
				
			||||||
@ -45,10 +44,6 @@ subroutine jt9a
 | 
				
			|||||||
  p_jt9=>address_jt9()
 | 
					  p_jt9=>address_jt9()
 | 
				
			||||||
  call jt9b(p_jt9,nbytes)
 | 
					  call jt9b(p_jt9,nbytes)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
!  write(*,1010) 
 | 
					 | 
				
			||||||
!1010 format('<jt9aFinished>')
 | 
					 | 
				
			||||||
!  flush(6)
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
100 inquire(file=trim(cwd)//'/.lock',exist=fileExists)
 | 
					100 inquire(file=trim(cwd)//'/.lock',exist=fileExists)
 | 
				
			||||||
  if(fileExists) go to 10
 | 
					  if(fileExists) go to 10
 | 
				
			||||||
  call sleep_msec(100)
 | 
					  call sleep_msec(100)
 | 
				
			||||||
 | 
				
			|||||||
@ -1,5 +1,9 @@
 | 
				
			|||||||
subroutine redsync(ss,ntrperiod,ihsym,iz,red)
 | 
					subroutine redsync(ss,ntrperiod,ihsym,iz,red)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					! Compute the red curve (approx JT9 sync amplitude).
 | 
				
			||||||
 | 
					! NB: red() is used for real-time display only.  A better ccfred() is
 | 
				
			||||||
 | 
					! computed during the decode procedure.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  Parameter (NSMAX=22000)
 | 
					  Parameter (NSMAX=22000)
 | 
				
			||||||
  real*4 ss(184,NSMAX)
 | 
					  real*4 ss(184,NSMAX)
 | 
				
			||||||
  real*4 red(NSMAX)
 | 
					  real*4 red(NSMAX)
 | 
				
			||||||
@ -11,9 +15,9 @@ subroutine redsync(ss,ntrperiod,ihsym,iz,red)
 | 
				
			|||||||
  if(ntrperiod.eq.10) lagmax=1
 | 
					  if(ntrperiod.eq.10) lagmax=1
 | 
				
			||||||
  if(ntrperiod.eq.30) lagmax=1
 | 
					  if(ntrperiod.eq.30) lagmax=1
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  do i=1,iz
 | 
					  do i=1,iz                                !Loop over frequency range
 | 
				
			||||||
     smax=0.
 | 
					     smax=0.
 | 
				
			||||||
     do lag=-lagmax,lagmax
 | 
					     do lag=-lagmax,lagmax                 !Loop over DT lags
 | 
				
			||||||
        sig=0.
 | 
					        sig=0.
 | 
				
			||||||
        do j=1,16
 | 
					        do j=1,16
 | 
				
			||||||
           k=ii2(j)+lag
 | 
					           k=ii2(j)+lag
 | 
				
			||||||
 | 
				
			|||||||
@ -1,6 +1,8 @@
 | 
				
			|||||||
subroutine decode9a(c0,npts8,nsps8,fpk,syncpk,snrdb,xdt,freq,drift,   &
 | 
					subroutine softsym(c0,npts8,nsps8,fpk,syncpk,snrdb,xdt,freq,drift,   &
 | 
				
			||||||
     i1SoftSymbols)
 | 
					     i1SoftSymbols)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					! Compute the soft symbols
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  complex c0(0:npts8-1)
 | 
					  complex c0(0:npts8-1)
 | 
				
			||||||
  complex c2(0:4096-1)
 | 
					  complex c2(0:4096-1)
 | 
				
			||||||
  complex c3(0:4096-1)
 | 
					  complex c3(0:4096-1)
 | 
				
			||||||
@ -13,23 +15,25 @@ subroutine decode9a(c0,npts8,nsps8,fpk,syncpk,snrdb,xdt,freq,drift,   &
 | 
				
			|||||||
  nspsd=16
 | 
					  nspsd=16
 | 
				
			||||||
  ndown=nsps8/nspsd
 | 
					  ndown=nsps8/nspsd
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! Downsample to 16 samples/symbol
 | 
					! Mix, low-pass filter, and downsample to 16 samples per symbol
 | 
				
			||||||
  call downsam9(c0,npts8,nsps8,nspsd,fpk,c2,nz2)
 | 
					  call downsam9(c0,npts8,nsps8,nspsd,fpk,c2,nz2)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  call peakdt9(c2,nz2,nsps8,nspsd,c3,nz3,xdt)
 | 
					  call peakdt9(c2,nz2,nsps8,nspsd,c3,nz3,xdt)  !Find DT
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  fsample=1500.0/ndown
 | 
					  fsample=1500.0/ndown
 | 
				
			||||||
  a=0.
 | 
					  a=0.
 | 
				
			||||||
  call afc9(c3,nz3,fsample,a,syncpk)
 | 
					  call afc9(c3,nz3,fsample,a,syncpk)  !Find deltaF, fDot, fDDot
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  call twkfreq(c3,c5,nz3,fsample,a)
 | 
					  call twkfreq(c3,c5,nz3,fsample,a)   !Correct for deltaF, fDot, fDDot
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					! Compute soft symbols (in scrambled order)
 | 
				
			||||||
  call symspec2(c5,nz3,nsps8,nspsd,fsample,snrdb,i1SoftSymbolsScrambled)
 | 
					  call symspec2(c5,nz3,nsps8,nspsd,fsample,snrdb,i1SoftSymbolsScrambled)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					! Remove interleaving
 | 
				
			||||||
  call interleave9(i1SoftSymbolsScrambled,-1,i1SoftSymbols)
 | 
					  call interleave9(i1SoftSymbolsScrambled,-1,i1SoftSymbols)
 | 
				
			||||||
  
 | 
					  
 | 
				
			||||||
  freq=fpk - a(1)
 | 
					  freq=fpk - a(1)
 | 
				
			||||||
  drift=-2.0*a(2)
 | 
					  drift=-2.0*a(2)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  return
 | 
					  return
 | 
				
			||||||
end subroutine decode9a
 | 
					end subroutine softsym
 | 
				
			||||||
@ -4,15 +4,16 @@ subroutine symspec(k,ntrperiod,nsps,ingain,nb,nbslider,pxdb,s,red,    &
 | 
				
			|||||||
! Input:
 | 
					! Input:
 | 
				
			||||||
!  k         pointer to the most recent new data
 | 
					!  k         pointer to the most recent new data
 | 
				
			||||||
!  ntrperiod T/R sequence length, minutes
 | 
					!  ntrperiod T/R sequence length, minutes
 | 
				
			||||||
!  nsps      samples per symbol (12000 Hz)
 | 
					!  nsps      samples per symbol, at 12000 Hz
 | 
				
			||||||
!  ndiskdat  0/1 to indicate if data from disk
 | 
					!  ndiskdat  0/1 to indicate if data from disk
 | 
				
			||||||
!  nb        0/1 status of noise blanker (off/on)
 | 
					!  nb        0/1 status of noise blanker (off/on)
 | 
				
			||||||
!  nbslider  NB setting, 0-100
 | 
					!  nbslider  NB setting, 0-100
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! Output:
 | 
					! Output:
 | 
				
			||||||
!  pxdb      power (0-60 dB)
 | 
					!  pxdb      power (0-60 dB)
 | 
				
			||||||
!  s         spectrum for waterfall display
 | 
					!  s()       spectrum for waterfall display
 | 
				
			||||||
!  ihsym     index number of this half-symbol (1-322)
 | 
					!  red()     first cut at JT9 sync amplitude
 | 
				
			||||||
 | 
					!  ihsym     index number of this half-symbol (1-184)
 | 
				
			||||||
!  nzap      number of samples zero'ed by noise blanker
 | 
					!  nzap      number of samples zero'ed by noise blanker
 | 
				
			||||||
!  slimit    NB scale adjustment
 | 
					!  slimit    NB scale adjustment
 | 
				
			||||||
!  lstrong   true if strong signal at this freq
 | 
					!  lstrong   true if strong signal at this freq
 | 
				
			||||||
@ -43,21 +44,21 @@ subroutine symspec(k,ntrperiod,nsps,ingain,nb,nbslider,pxdb,s,red,    &
 | 
				
			|||||||
  if(ntrperiod.eq.10) nfft3=12288
 | 
					  if(ntrperiod.eq.10) nfft3=12288
 | 
				
			||||||
  if(ntrperiod.eq.30) nfft3=32768
 | 
					  if(ntrperiod.eq.30) nfft3=32768
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  jstep=nsps/16
 | 
					  jstep=nsps/16                                !Step size = half-symbol in c0()
 | 
				
			||||||
  if(k.gt.NMAX) go to 999
 | 
					  if(k.gt.NMAX) go to 999
 | 
				
			||||||
  if(k.lt.nfft3) then
 | 
					  if(k.lt.nfft3) then
 | 
				
			||||||
     ihsym=0
 | 
					     ihsym=0
 | 
				
			||||||
     go to 999                                 !Wait for enough samples to start
 | 
					     go to 999                                 !Wait for enough samples to start
 | 
				
			||||||
  endif
 | 
					  endif
 | 
				
			||||||
  if(nfft3.ne.nfft3z) then
 | 
					  if(nfft3.ne.nfft3z) then                     !New nfft3, compute window
 | 
				
			||||||
     pi=4.0*atan(1.0)
 | 
					     pi=4.0*atan(1.0)
 | 
				
			||||||
     do i=1,nfft3
 | 
					     do i=1,nfft3
 | 
				
			||||||
        w3(i)=2.0*(sin(i*pi/nfft3))**2             !Window for nfft3
 | 
					        w3(i)=2.0*(sin(i*pi/nfft3))**2         !Window for nfft3 spectrum
 | 
				
			||||||
     enddo
 | 
					     enddo
 | 
				
			||||||
     nfft3z=nfft3
 | 
					     nfft3z=nfft3
 | 
				
			||||||
  endif
 | 
					  endif
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  if(k.lt.k0) then
 | 
					  if(k.lt.k0) then                             !Start a new data block
 | 
				
			||||||
     ja=0
 | 
					     ja=0
 | 
				
			||||||
     ssum=0.
 | 
					     ssum=0.
 | 
				
			||||||
     ihsym=0
 | 
					     ihsym=0
 | 
				
			||||||
@ -116,10 +117,10 @@ subroutine symspec(k,ntrperiod,nsps,ingain,nb,nbslider,pxdb,s,red,    &
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
  if(ihsym.lt.184) ihsym=ihsym+1
 | 
					  if(ihsym.lt.184) ihsym=ihsym+1
 | 
				
			||||||
  cx(0:nfft3-1)=w3(1:nfft3)*cx(0:nfft3-1)  !Apply window w3
 | 
					  cx(0:nfft3-1)=w3(1:nfft3)*cx(0:nfft3-1)  !Apply window w3
 | 
				
			||||||
  call four2a(cx,nfft3,1,1,1)           !Third forward FFT (X)
 | 
					  call four2a(cx,nfft3,1,1,1)              !Third FFT (forward)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  n=min(184,ihsym)
 | 
					  n=min(184,ihsym)
 | 
				
			||||||
  df3=1500.0/nfft3
 | 
					  df3=1500.0/nfft3                    !JT9-a: 0.732 Hz = 0.42 * tone spacing
 | 
				
			||||||
  i0=nint(-500.0/df3)
 | 
					  i0=nint(-500.0/df3)
 | 
				
			||||||
  iz=min(NSMAX,nint(1000.0/df3))
 | 
					  iz=min(NSMAX,nint(1000.0/df3))
 | 
				
			||||||
  fac=(1.0/nfft3)**2
 | 
					  fac=(1.0/nfft3)**2
 | 
				
			||||||
 | 
				
			|||||||
@ -1,5 +1,7 @@
 | 
				
			|||||||
subroutine symspec2(c5,nz3,nsps8,nspsd,fsample,snrdb,i1SoftSymbolsScrambled)
 | 
					subroutine symspec2(c5,nz3,nsps8,nspsd,fsample,snrdb,i1SoftSymbolsScrambled)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					! Compute soft symbols from the final downsampled data
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  complex c5(0:4096-1)
 | 
					  complex c5(0:4096-1)
 | 
				
			||||||
  complex z
 | 
					  complex z
 | 
				
			||||||
  integer*1 i1SoftSymbolsScrambled(207)
 | 
					  integer*1 i1SoftSymbolsScrambled(207)
 | 
				
			||||||
@ -13,20 +15,20 @@ subroutine symspec2(c5,nz3,nsps8,nspsd,fsample,snrdb,i1SoftSymbolsScrambled)
 | 
				
			|||||||
  aa(1)=-1500.0/nsps8
 | 
					  aa(1)=-1500.0/nsps8
 | 
				
			||||||
  aa(2)=0.
 | 
					  aa(2)=0.
 | 
				
			||||||
  aa(3)=0.
 | 
					  aa(3)=0.
 | 
				
			||||||
  do i=0,8
 | 
					  do i=0,8                                         !Loop over the 9 tones
 | 
				
			||||||
     if(i.ge.1) call twkfreq(c5,c5,nz3,fsample,aa)
 | 
					     if(i.ge.1) call twkfreq(c5,c5,nz3,fsample,aa)
 | 
				
			||||||
     m=0
 | 
					     m=0
 | 
				
			||||||
     k=-1
 | 
					     k=-1
 | 
				
			||||||
     do j=1,85
 | 
					     do j=1,85                                     !Loop over all symbols
 | 
				
			||||||
        z=0.
 | 
					        z=0.
 | 
				
			||||||
        do n=1,nspsd
 | 
					        do n=1,nspsd                               !Sum over 16 samples
 | 
				
			||||||
           k=k+1
 | 
					           k=k+1
 | 
				
			||||||
           z=z+c5(k)
 | 
					           z=z+c5(k)
 | 
				
			||||||
        enddo
 | 
					        enddo
 | 
				
			||||||
        ss2(i,j)=real(z)**2 + aimag(z)**2
 | 
					        ss2(i,j)=real(z)**2 + aimag(z)**2        !Symbol speactra, data and sync
 | 
				
			||||||
        if(i.ge.1 .and. isync(j).eq.0) then
 | 
					        if(i.ge.1 .and. isync(j).eq.0) then
 | 
				
			||||||
           m=m+1
 | 
					           m=m+1
 | 
				
			||||||
           ss3(i-1,m)=ss2(i,j)
 | 
					           ss3(i-1,m)=ss2(i,j)                   !Symbol speactra, data only
 | 
				
			||||||
        endif
 | 
					        endif
 | 
				
			||||||
     enddo
 | 
					     enddo
 | 
				
			||||||
  enddo
 | 
					  enddo
 | 
				
			||||||
@ -43,11 +45,10 @@ subroutine symspec2(c5,nz3,nsps8,nspsd,fsample,snrdb,i1SoftSymbolsScrambled)
 | 
				
			|||||||
     sig=sig+smax
 | 
					     sig=sig+smax
 | 
				
			||||||
     ss=ss-smax
 | 
					     ss=ss-smax
 | 
				
			||||||
  enddo
 | 
					  enddo
 | 
				
			||||||
  ave=ss/(69*7) 
 | 
					  ave=ss/(69*7)                           !Baseline
 | 
				
			||||||
  call pctile(ss2,9*85,35,xmed)
 | 
					  call pctile(ss2,9*85,35,xmed)
 | 
				
			||||||
  ss3=ss3/ave
 | 
					  ss3=ss3/ave
 | 
				
			||||||
 | 
					  sig=sig/69.                             !Signal
 | 
				
			||||||
  sig=sig/69.
 | 
					 | 
				
			||||||
  t=max(1.0,sig - 1.0)
 | 
					  t=max(1.0,sig - 1.0)
 | 
				
			||||||
  snrdb=db(t) - 61.3
 | 
					  snrdb=db(t) - 61.3
 | 
				
			||||||
     
 | 
					     
 | 
				
			||||||
 | 
				
			|||||||
@ -15,11 +15,11 @@ subroutine sync9(ss,nzhsym,tstep,df3,nfa,nfb,ccfred,ia,ib,ipkbest)
 | 
				
			|||||||
  lag2=5.0/tstep + 0.9999
 | 
					  lag2=5.0/tstep + 0.9999
 | 
				
			||||||
  ccfred=0.
 | 
					  ccfred=0.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  do i=ia,ib
 | 
					  do i=ia,ib                         !Loop over freq range
 | 
				
			||||||
     smax=0.
 | 
					     smax=0.
 | 
				
			||||||
     do lag=lag1,lag2
 | 
					     do lag=lag1,lag2                !DT = 2.5 to 5.0 s
 | 
				
			||||||
        sum=0.
 | 
					        sum=0.
 | 
				
			||||||
        do j=1,16
 | 
					        do j=1,16                    !Sum over 16 sync symbols
 | 
				
			||||||
           k=ii2(j) + lag
 | 
					           k=ii2(j) + lag
 | 
				
			||||||
           kaa=ka(j)+lag
 | 
					           kaa=ka(j)+lag
 | 
				
			||||||
           kbb=kb(j)+lag
 | 
					           kbb=kb(j)+lag
 | 
				
			||||||
 | 
				
			|||||||
@ -1372,7 +1372,11 @@ void MainWindow::on_EraseButton_clicked()                          //Erase
 | 
				
			|||||||
{
 | 
					{
 | 
				
			||||||
  qint64 ms=QDateTime::currentMSecsSinceEpoch();
 | 
					  qint64 ms=QDateTime::currentMSecsSinceEpoch();
 | 
				
			||||||
  ui->decodedTextBrowser->clear();
 | 
					  ui->decodedTextBrowser->clear();
 | 
				
			||||||
  if((ms-m_msErase)<500) ui->decodedTextBrowser2->clear();
 | 
					  if((ms-m_msErase)<500) {
 | 
				
			||||||
 | 
					      ui->decodedTextBrowser2->clear();
 | 
				
			||||||
 | 
					      QFile f(m_appDir + "/decoded.txt");
 | 
				
			||||||
 | 
					      if(f.exists()) f.remove();
 | 
				
			||||||
 | 
					  }
 | 
				
			||||||
  m_msErase=ms;
 | 
					  m_msErase=ms;
 | 
				
			||||||
}
 | 
					}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user