mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-11-03 21:40:52 -05:00 
			
		
		
		
	Temporary mode QRA02 is now basically functional (though buggy).
git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@6833 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
		
							parent
							
								
									c864766332
								
							
						
					
					
						commit
						0384d312a6
					
				@ -411,6 +411,7 @@ set (wsjt_FSRCS
 | 
			
		||||
  lib/polyfit.f90
 | 
			
		||||
  lib/prog_args.f90
 | 
			
		||||
  lib/ps4.f90
 | 
			
		||||
  lib/qra02.f90
 | 
			
		||||
  lib/readwav.f90
 | 
			
		||||
  lib/rectify_msk.f90
 | 
			
		||||
  lib/refspectrum.f90
 | 
			
		||||
 | 
			
		||||
@ -233,7 +233,7 @@ contains
 | 
			
		||||
    integer, intent(in) :: nsum
 | 
			
		||||
    integer, intent(in) :: minsync
 | 
			
		||||
 | 
			
		||||
    integer i
 | 
			
		||||
    integer i,nft
 | 
			
		||||
    logical is_deep,is_average
 | 
			
		||||
    character decoded*22,csync*2,cflags*3
 | 
			
		||||
 | 
			
		||||
@ -242,6 +242,18 @@ contains
 | 
			
		||||
    decoded=decoded0
 | 
			
		||||
    cflags='   '
 | 
			
		||||
    is_deep=ft.eq.2
 | 
			
		||||
 | 
			
		||||
    if(ft.ge.80) then
 | 
			
		||||
       nft=ft-100
 | 
			
		||||
       csync=':'
 | 
			
		||||
       write(*,1009) params%nutc,snr,dt,freq,csync,decoded,nft
 | 
			
		||||
1009   format(i4.4,i4,f5.1,i5,1x,a2,1x,a22,i2)
 | 
			
		||||
       write(13,1011) params%nutc,nint(sync),snr,dt,float(freq),drift,    &
 | 
			
		||||
            decoded,nft
 | 
			
		||||
1011   format(i4.4,i4,i5,f6.2,f8.0,i4,3x,a22,' QRA65',i3)
 | 
			
		||||
       go to 100
 | 
			
		||||
    endif
 | 
			
		||||
 | 
			
		||||
    if(ft.eq.0 .and. minsync.ge.0 .and. int(sync).lt.minsync) then
 | 
			
		||||
       write(*,1010) params%nutc,snr,dt,freq
 | 
			
		||||
    else
 | 
			
		||||
@ -275,19 +287,14 @@ contains
 | 
			
		||||
             endif
 | 
			
		||||
          endif
 | 
			
		||||
       endif
 | 
			
		||||
       if(ft.ge.100) then
 | 
			
		||||
          write(*,1009) params%nutc,snr,dt,freq,csync,decoded,ft-100
 | 
			
		||||
1009      format(i4.4,i4,f5.1,i5,1x,a2,1x,a22,i2)
 | 
			
		||||
       else
 | 
			
		||||
       write(*,1010) params%nutc,snr,dt,freq,csync,decoded,cflags
 | 
			
		||||
1010   format(i4.4,i4,f5.1,i5,1x,a2,1x,a22,1x,a3)
 | 
			
		||||
    endif
 | 
			
		||||
    endif
 | 
			
		||||
 | 
			
		||||
    write(13,1012) params%nutc,nint(sync),snr,dt,float(freq),drift,    &
 | 
			
		||||
         decoded,ft,nsum,nsmo
 | 
			
		||||
1012 format(i4.4,i4,i5,f6.2,f8.0,i4,3x,a22,' JT65',3i3)
 | 
			
		||||
    call flush(6)
 | 
			
		||||
 | 
			
		||||
100 call flush(6)
 | 
			
		||||
 | 
			
		||||
!$omp end critical(decode_results)
 | 
			
		||||
    select type(this)
 | 
			
		||||
 | 
			
		||||
@ -61,20 +61,6 @@ subroutine extract(s3,nadd,mode65,ntrials,naggressive,ndepth,nflip,     &
 | 
			
		||||
     go to 1
 | 
			
		||||
  endif
 | 
			
		||||
 | 
			
		||||
  if(mode65.eq.101) then
 | 
			
		||||
     call packcall(mycall,nmycall,ltext)
 | 
			
		||||
     call qra65_dec(s3,nmycall,dat4,irc)       !Attempt decoding
 | 
			
		||||
     decoded="                      "
 | 
			
		||||
     if(irc.ge.0) then
 | 
			
		||||
        call unpackmsg(dat4,decoded)           !Unpack the user message
 | 
			
		||||
        call fmtmsg(decoded,iz)
 | 
			
		||||
        nft=100 + irc
 | 
			
		||||
     else
 | 
			
		||||
        dec=0
 | 
			
		||||
     endif
 | 
			
		||||
     go to 900
 | 
			
		||||
  endif
 | 
			
		||||
 | 
			
		||||
  mrs=mrsym
 | 
			
		||||
  mrs2=mr2sym
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
@ -96,6 +96,25 @@ contains
 | 
			
		||||
    robust=nrobust
 | 
			
		||||
    dd=dd0
 | 
			
		||||
    ndecoded=0
 | 
			
		||||
 | 
			
		||||
    if(nsubmode.ge.100) then
 | 
			
		||||
! This is QRA65 mode
 | 
			
		||||
!       print*,'A',nsubmode,nsubmode,nsubmode
 | 
			
		||||
       call qra02(dd,nf1,nf2,nfqso,ntol,mycall,sync,nsnr,dtx,nfreq,decoded,nft)
 | 
			
		||||
!       print*,'Z',nft,decoded
 | 
			
		||||
       if (associated(this%callback)) then
 | 
			
		||||
          ndrift=0
 | 
			
		||||
          nflip=1
 | 
			
		||||
          width=1.0
 | 
			
		||||
          nsmo=0
 | 
			
		||||
          nqual=0
 | 
			
		||||
          call this%callback(sync,nsnr,dtx,nfreq,ndrift,  &
 | 
			
		||||
               nflip,width,decoded,nft,nqual,nsmo,1,minsync)
 | 
			
		||||
       end if
 | 
			
		||||
 | 
			
		||||
       go to 900
 | 
			
		||||
    endif
 | 
			
		||||
 | 
			
		||||
    do ipass=1,n2pass                             !Two-pass decoding loop
 | 
			
		||||
       first_time=.true.
 | 
			
		||||
       if(ipass.eq.1) then                        !First-pass parameters
 | 
			
		||||
@ -163,9 +182,7 @@ contains
 | 
			
		||||
          nvec=100
 | 
			
		||||
       endif
 | 
			
		||||
 | 
			
		||||
       if(nsubmode.le.8) mode65=2**nsubmode
 | 
			
		||||
       if(nsubmode.eq.101) mode65=101
 | 
			
		||||
 | 
			
		||||
       mode65=2**nsubmode
 | 
			
		||||
       nflip=1
 | 
			
		||||
       nqd=0
 | 
			
		||||
       decoded='                      '
 | 
			
		||||
@ -298,7 +315,7 @@ contains
 | 
			
		||||
       if(ndecoded.lt.1) exit
 | 
			
		||||
    enddo                                    !Two-pass loop
 | 
			
		||||
 | 
			
		||||
    return
 | 
			
		||||
900 return
 | 
			
		||||
  end subroutine decode
 | 
			
		||||
 | 
			
		||||
  subroutine avg65(nutc,nsave,snrsync,dtxx,nflip,nfreq,mode65,ntol,ndepth,    &
 | 
			
		||||
 | 
			
		||||
@ -24,19 +24,13 @@ void qra65_dec_(float r[], int* nmycall, int xdec[], int* rc)
 | 
			
		||||
//   rc=4    [CALL ?     ] AP44
 | 
			
		||||
//   rc=5    [CALL CALL ?] AP57
 | 
			
		||||
 | 
			
		||||
  static int ncall0=0;
 | 
			
		||||
  int ncall;
 | 
			
		||||
  int x[63],y[12];
 | 
			
		||||
  static ncall0=-1;
 | 
			
		||||
  int ncall=*nmycall;
 | 
			
		||||
  static qra65codec *codec;
 | 
			
		||||
 | 
			
		||||
  ncall = *nmycall;
 | 
			
		||||
  qra65codec *codec = qra65_init(1,ncall);	//codec for ncall
 | 
			
		||||
/*
 | 
			
		||||
  if(ncall!=ncall0) {
 | 
			
		||||
    memset(y,0,sizeof(y));
 | 
			
		||||
    qra65_encode(codec, y, x);
 | 
			
		||||
    printf("Updated codec %d\n",ncall);
 | 
			
		||||
  }
 | 
			
		||||
    codec = qra65_init(1,ncall);	//codec for ncall
 | 
			
		||||
    ncall0=ncall;
 | 
			
		||||
*/
 | 
			
		||||
  }
 | 
			
		||||
  *rc = qra65_decode(codec,xdec,r);
 | 
			
		||||
}
 | 
			
		||||
 | 
			
		||||
							
								
								
									
										151
									
								
								lib/qra02.f90
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										151
									
								
								lib/qra02.f90
									
									
									
									
									
										Normal file
									
								
							@ -0,0 +1,151 @@
 | 
			
		||||
subroutine qra02(dd,nf1,nf2,nfqso,ntol,mycall_12,sync,nsnr,dtx,nfreq,    &
 | 
			
		||||
     decoded,nft)
 | 
			
		||||
 | 
			
		||||
  use packjt
 | 
			
		||||
  parameter (NFFT=2*6912,NH=NFFT/2,NZ=5760)
 | 
			
		||||
  character decoded*22,mycall_12*12,mycall*6
 | 
			
		||||
  character*1 mark(0:5),zplot(0:63)
 | 
			
		||||
  logical ltext
 | 
			
		||||
  integer icos7(0:6)
 | 
			
		||||
  integer ipk(1)
 | 
			
		||||
  integer jpk(1)
 | 
			
		||||
!  integer dat4(12)
 | 
			
		||||
  integer dat4(120)
 | 
			
		||||
  real dd(60*12000)
 | 
			
		||||
  real s(NZ)
 | 
			
		||||
  real savg(NZ)
 | 
			
		||||
  real blue(0:25)
 | 
			
		||||
  real red(NZ)
 | 
			
		||||
  real x(NFFT)
 | 
			
		||||
  complex cx(0:NH)
 | 
			
		||||
  equivalence (x,cx)
 | 
			
		||||
  data icos7/2,5,6,0,4,1,3/                            !Costas 7x7 pattern
 | 
			
		||||
  data mark/' ','.','-','+','X','$'/
 | 
			
		||||
  common/qra65com/ss(NZ,194),s3(0:63,1:63),ccf(NZ,0:25)
 | 
			
		||||
  save
 | 
			
		||||
 | 
			
		||||
!  rewind 74
 | 
			
		||||
!  rewind 75
 | 
			
		||||
 | 
			
		||||
!  print*,'B',nf1,nf2,nfqso,ntol
 | 
			
		||||
  nsps=6912
 | 
			
		||||
  istep=nsps/2
 | 
			
		||||
  nsteps=52*12000/istep - 2
 | 
			
		||||
  ia=1-istep
 | 
			
		||||
  savg=0.
 | 
			
		||||
  df=12000.0/NFFT
 | 
			
		||||
  do j=1,nsteps
 | 
			
		||||
     ia=ia+istep
 | 
			
		||||
     ib=ia+nsps-1
 | 
			
		||||
     x(1:nsps)=1.2e-4*dd(ia:ib)
 | 
			
		||||
     x(nsps+1:)=0.0
 | 
			
		||||
     call four2a(x,nfft,1,-1,0)        !r2c FFT
 | 
			
		||||
     do i=1,NZ
 | 
			
		||||
        s(i)=real(cx(i))**2 + aimag(cx(i))**2
 | 
			
		||||
     enddo
 | 
			
		||||
     ss(1:NZ,j)=s
 | 
			
		||||
     savg=savg+s
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
  savg=savg/nsteps
 | 
			
		||||
  call pctile(savg,NZ,45,base)
 | 
			
		||||
  savg=savg/base - 1.0
 | 
			
		||||
  ss=ss/base
 | 
			
		||||
!  do i=1,NZ
 | 
			
		||||
!     write(73,1010) i*df,savg(i),i
 | 
			
		||||
!1010 format(2f10.3,i8)
 | 
			
		||||
!  enddo
 | 
			
		||||
 | 
			
		||||
  fa=max(nf1,nfqso-ntol)
 | 
			
		||||
  fb=min(nf2,nfqso+ntol)
 | 
			
		||||
  ia=nint(fa/df)
 | 
			
		||||
  ib=nint(fb/df)
 | 
			
		||||
  fac=1.0/sqrt(21.0)
 | 
			
		||||
  sync=0.
 | 
			
		||||
  do if0=ia,ib
 | 
			
		||||
     red(if0)=0.
 | 
			
		||||
     do j=0,25
 | 
			
		||||
        t=-3.0
 | 
			
		||||
        do n=0,6
 | 
			
		||||
           i=if0 + 2*icos7(n)
 | 
			
		||||
           t=t + ss(i,1+2*n+j) + ss(i,1+2*n+j+78) + ss(i,1+2*n+j+154)
 | 
			
		||||
        enddo
 | 
			
		||||
        ccf(if0,j)=fac*t
 | 
			
		||||
        if(ccf(if0,j).gt.red(if0)) then
 | 
			
		||||
           red(if0)=ccf(if0,j)
 | 
			
		||||
           if(red(if0).gt.sync) then
 | 
			
		||||
              sync=red(if0)
 | 
			
		||||
              f0=if0*df
 | 
			
		||||
              dtx=j*istep/12000.0 - 1.0
 | 
			
		||||
              i0=if0
 | 
			
		||||
              j0=j
 | 
			
		||||
           endif
 | 
			
		||||
        endif
 | 
			
		||||
     enddo
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
  do i=0,63
 | 
			
		||||
     k=i0 + 2*i
 | 
			
		||||
     jj=j0+13
 | 
			
		||||
     do j=1,63
 | 
			
		||||
        jj=jj+2
 | 
			
		||||
        s3(i,j)=ss(k,jj)
 | 
			
		||||
        if(j.eq.32) jj=jj+14               !Skip over the middle Costas array
 | 
			
		||||
     enddo
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
  do j=1,63
 | 
			
		||||
     do i=0,63
 | 
			
		||||
        n=0.25*s3(i,j)
 | 
			
		||||
        if(n.lt.0) n=0
 | 
			
		||||
        if(n.gt.5) n=5
 | 
			
		||||
        zplot(i)=mark(n)
 | 
			
		||||
     enddo
 | 
			
		||||
     ipk=maxloc(s3(0:63,j))
 | 
			
		||||
!     write(76,3001) j,zplot,ipk(1)-1
 | 
			
		||||
!3001 format(i2,1x,'|',64a1,'|',i4)
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
  if0=nint(f0/df)
 | 
			
		||||
  nfreq=nint(f0)
 | 
			
		||||
  blue(0:25)=ccf(if0,0:25)
 | 
			
		||||
  jpk=maxloc(blue)
 | 
			
		||||
  xpk=jpk(1) + 1.0
 | 
			
		||||
  call slope(blue,26,xpk)
 | 
			
		||||
 | 
			
		||||
!  do j=0,25
 | 
			
		||||
!     tsec=j*istep/12000.0
 | 
			
		||||
!     write(74,1020) tsec,blue(j)
 | 
			
		||||
!1020 format(f5.2,i3,10f7.1)
 | 
			
		||||
!  enddo
 | 
			
		||||
 | 
			
		||||
!  do i=ia,ib
 | 
			
		||||
!     f=i*df
 | 
			
		||||
!     write(75,1030) f,red(i)
 | 
			
		||||
!1030 format(2f10.2)
 | 
			
		||||
!  enddo
 | 
			
		||||
!  flush(74)
 | 
			
		||||
!  flush(75)
 | 
			
		||||
!  flush(76)
 | 
			
		||||
 | 
			
		||||
  nsnr=-30
 | 
			
		||||
  if(sync.gt.1.0) nsnr=nint(10.0*log10(sync) - 38.0)
 | 
			
		||||
 | 
			
		||||
  decoded='                      '
 | 
			
		||||
  nft=100
 | 
			
		||||
  mycall=mycall_12(1:6)                     !### May need fixing ###
 | 
			
		||||
  call packcall(mycall,nmycall,ltext)
 | 
			
		||||
!  write(77,3002) s3
 | 
			
		||||
!3002 format(f10.3)
 | 
			
		||||
!  flush(77)
 | 
			
		||||
!  print*,'a',sync,dtx,base
 | 
			
		||||
  call qra65_dec(s3,nmycall,dat4,irc)       !Attempt decoding
 | 
			
		||||
!  print*,'z',sync,dtx,nfreq
 | 
			
		||||
  if(irc.ge.0) then
 | 
			
		||||
     call unpackmsg(dat4,decoded)           !Unpack the user message
 | 
			
		||||
     call fmtmsg(decoded,iz)
 | 
			
		||||
     nft=100 + irc
 | 
			
		||||
  endif
 | 
			
		||||
 | 
			
		||||
  return
 | 
			
		||||
end subroutine qra02
 | 
			
		||||
@ -4727,7 +4727,6 @@ void MainWindow::transmit (double snr)
 | 
			
		||||
    if(m_nSubMode==0) toneSpacing=12000.0/6912.0;
 | 
			
		||||
    if(m_nSubMode==1) toneSpacing=2*12000.0/6912.0;
 | 
			
		||||
    if(m_nSubMode==2) toneSpacing=4*12000.0/6912.0;
 | 
			
		||||
    qDebug() << "b" << m_modeTx << itone[0]<< itone[1]<< itone[2]<< itone[3]<< itone[4]<< itone[5] ;
 | 
			
		||||
    Q_EMIT sendMessage (NUM_QRA65_SYMBOLS,
 | 
			
		||||
           6912.0, ui->TxFreqSpinBox->value () - m_XIT,
 | 
			
		||||
           toneSpacing, m_soundOutput, m_config.audio_output_channel (),
 | 
			
		||||
 | 
			
		||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user