mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-11-03 21:40:52 -05:00 
			
		
		
		
	Further improvements to JT9 decoder.
Better AFC (wider range of possible drifts; more accurate DT alignment). Better definition of metric tables used by Fano decoder. Zero-centeres soft symbols, instead of offset +128. Tuned several empirical parameters. git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@5004 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
		
							parent
							
								
									127a60be68
								
							
						
					
					
						commit
						79538977c7
					
				
							
								
								
									
										26
									
								
								lib/afc9.f90
									
									
									
									
									
								
							
							
						
						
									
										26
									
								
								lib/afc9.f90
									
									
									
									
									
								
							@ -1,25 +1,32 @@
 | 
				
			|||||||
subroutine afc9(c3,npts,fsample,a,syncpk)
 | 
					subroutine afc9(c3a,npts,fsample,a,syncpk)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  complex c3(0:npts-1)
 | 
					  complex c3a(0:npts-1)
 | 
				
			||||||
 | 
					  complex c3(0:1360-1)
 | 
				
			||||||
  real a(3),deltaa(3)
 | 
					  real a(3),deltaa(3)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  a(1)=0.                                   !f0
 | 
					  a(1)=0.                                   !f0
 | 
				
			||||||
  a(2)=0.                                   !f1
 | 
					  a(2)=0.                                   !f1
 | 
				
			||||||
  a(3)=0.                                   !f2
 | 
					  a(3)=0.                                   !f2
 | 
				
			||||||
  deltaa(1)=0.4
 | 
					  deltaa(1)=1.736
 | 
				
			||||||
  deltaa(2)=0.1
 | 
					  deltaa(2)=1.736
 | 
				
			||||||
  deltaa(3)=0.1
 | 
					  deltaa(3)=1.0
 | 
				
			||||||
  nterms=3
 | 
					  nterms=3
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! Start the iteration
 | 
					! Start the iteration
 | 
				
			||||||
  chisqr=0.
 | 
					  chisqr=0.
 | 
				
			||||||
  chisqr0=1.e6
 | 
					  chisqr0=1.e6
 | 
				
			||||||
  do iter=1,4                               !One iteration is enough?
 | 
					  c3=c3a
 | 
				
			||||||
 | 
					  a3=a(3)
 | 
				
			||||||
 | 
					  do iter=1,4
 | 
				
			||||||
     do j=1,nterms
 | 
					     do j=1,nterms
 | 
				
			||||||
 | 
					        if(a(3).ne.a3) c3=cshift(c3a,nint(a(3)))
 | 
				
			||||||
 | 
					        a3=a(3)
 | 
				
			||||||
        chisq1=fchisq(c3,npts,fsample,a)
 | 
					        chisq1=fchisq(c3,npts,fsample,a)
 | 
				
			||||||
        fn=0.
 | 
					        fn=0.
 | 
				
			||||||
        delta=deltaa(j)
 | 
					        delta=deltaa(j)
 | 
				
			||||||
10      a(j)=a(j)+delta
 | 
					10      a(j)=a(j)+delta
 | 
				
			||||||
 | 
					        if(a(3).ne.a3) c3=cshift(c3a,nint(a(3)))
 | 
				
			||||||
 | 
					        a3=a(3)
 | 
				
			||||||
        chisq2=fchisq(c3,npts,fsample,a)
 | 
					        chisq2=fchisq(c3,npts,fsample,a)
 | 
				
			||||||
        if(chisq2.eq.chisq1) go to 10
 | 
					        if(chisq2.eq.chisq1) go to 10
 | 
				
			||||||
        if(chisq2.gt.chisq1) then
 | 
					        if(chisq2.gt.chisq1) then
 | 
				
			||||||
@ -31,6 +38,8 @@ subroutine afc9(c3,npts,fsample,a,syncpk)
 | 
				
			|||||||
        endif
 | 
					        endif
 | 
				
			||||||
20      fn=fn+1.0
 | 
					20      fn=fn+1.0
 | 
				
			||||||
        a(j)=a(j)+delta
 | 
					        a(j)=a(j)+delta
 | 
				
			||||||
 | 
					        if(a(3).ne.a3) c3=cshift(c3a,nint(a(3)))
 | 
				
			||||||
 | 
					        a3=a(3)
 | 
				
			||||||
        chisq3=fchisq(c3,npts,fsample,a)
 | 
					        chisq3=fchisq(c3,npts,fsample,a)
 | 
				
			||||||
        if(chisq3.lt.chisq2) then
 | 
					        if(chisq3.lt.chisq2) then
 | 
				
			||||||
           chisq1=chisq2
 | 
					           chisq1=chisq2
 | 
				
			||||||
@ -41,16 +50,19 @@ subroutine afc9(c3,npts,fsample,a,syncpk)
 | 
				
			|||||||
! Find minimum of parabola defined by last three points
 | 
					! Find minimum of parabola defined by last three points
 | 
				
			||||||
        delta=delta*(1./(1.+(chisq1-chisq2)/(chisq3-chisq2))+0.5)
 | 
					        delta=delta*(1./(1.+(chisq1-chisq2)/(chisq3-chisq2))+0.5)
 | 
				
			||||||
        a(j)=a(j)-delta
 | 
					        a(j)=a(j)-delta
 | 
				
			||||||
        deltaa(j)=deltaa(j)*fn/3.
 | 
					        if(j.lt.3) deltaa(j)=deltaa(j)*fn/3.
 | 
				
			||||||
!        write(*,4000) iter,j,a,-chisq2
 | 
					!        write(*,4000) iter,j,a,-chisq2
 | 
				
			||||||
!4000    format(i1,i2,3f10.4,f11.3)
 | 
					!4000    format(i1,i2,3f10.4,f11.3)
 | 
				
			||||||
     enddo
 | 
					     enddo
 | 
				
			||||||
 | 
					     if(a(3).ne.a3) c3=cshift(c3a,nint(a(3)))
 | 
				
			||||||
 | 
					     a3=a(3)
 | 
				
			||||||
     chisqr=fchisq(c3,npts,fsample,a)
 | 
					     chisqr=fchisq(c3,npts,fsample,a)
 | 
				
			||||||
     if(chisqr/chisqr0.gt.0.99) exit
 | 
					     if(chisqr/chisqr0.gt.0.99) exit
 | 
				
			||||||
     chisqr0=chisqr
 | 
					     chisqr0=chisqr
 | 
				
			||||||
  enddo
 | 
					  enddo
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  syncpk=-chisqr
 | 
					  syncpk=-chisqr
 | 
				
			||||||
 | 
					  c3a=c3
 | 
				
			||||||
!  write(*,4001) a,-chisq2
 | 
					!  write(*,4001) a,-chisq2
 | 
				
			||||||
!4001 format(3x,3f10.4,f11.3)
 | 
					!4001 format(3x,3f10.4,f11.3)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
@ -4,13 +4,14 @@ subroutine decjt9(ss,id2,nutc,nfqso,newdat,npts8,nfa,nfsplit,nfb,ntol,  &
 | 
				
			|||||||
  include 'constants.f90'
 | 
					  include 'constants.f90'
 | 
				
			||||||
  real ss(184,NSMAX)
 | 
					  real ss(184,NSMAX)
 | 
				
			||||||
  character*22 msg
 | 
					  character*22 msg
 | 
				
			||||||
 | 
					  character*500 infile
 | 
				
			||||||
  real*4 ccfred(NSMAX)
 | 
					  real*4 ccfred(NSMAX)
 | 
				
			||||||
  real*4 red2(NSMAX)
 | 
					  real*4 red2(NSMAX)
 | 
				
			||||||
  logical ccfok(NSMAX)
 | 
					  logical ccfok(NSMAX)
 | 
				
			||||||
  logical done(NSMAX)
 | 
					  logical done(NSMAX)
 | 
				
			||||||
  integer*2 id2(NTMAX*12000)
 | 
					  integer*2 id2(NTMAX*12000)
 | 
				
			||||||
  integer*1 i1SoftSymbols(207)
 | 
					  integer*1 i1SoftSymbols(207)
 | 
				
			||||||
  common/decstats/num65,numbm,numkv,num9,numfano
 | 
					  common/decstats/num65,numbm,numkv,num9,numfano,infile
 | 
				
			||||||
  save ccfred,red2
 | 
					  save ccfred,red2
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  nsynced=0
 | 
					  nsynced=0
 | 
				
			||||||
@ -92,14 +93,12 @@ subroutine decjt9(ss,id2,nutc,nfqso,newdat,npts8,nfa,nfsplit,nfb,ntol,  &
 | 
				
			|||||||
           call timer('softsym ',0)
 | 
					           call timer('softsym ',0)
 | 
				
			||||||
           fpk=nf0 + df3*(i-1)
 | 
					           fpk=nf0 + df3*(i-1)
 | 
				
			||||||
           call softsym(id2,npts8,nsps8,newdat,fpk,syncpk,snrdb,xdt,    &
 | 
					           call softsym(id2,npts8,nsps8,newdat,fpk,syncpk,snrdb,xdt,    &
 | 
				
			||||||
                freq,drift,schk,i1SoftSymbols)
 | 
					                freq,drift,a3,schk,i1SoftSymbols)
 | 
				
			||||||
           call timer('softsym ',1)
 | 
					           call timer('softsym ',1)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
           sync=(syncpk+1)/4.0
 | 
					           sync=(syncpk+1)/4.0
 | 
				
			||||||
!           if(maxval(i1SoftSymbols).eq.0) cycle
 | 
					 | 
				
			||||||
           if(nqd.eq.1 .and. ((sync.lt.0.5) .or. (schk.lt.1.0))) cycle
 | 
					           if(nqd.eq.1 .and. ((sync.lt.0.5) .or. (schk.lt.1.0))) cycle
 | 
				
			||||||
           if(nqd.ne.1 .and. ((sync.lt.1.0) .or. (schk.lt.1.5))) cycle
 | 
					           if(nqd.ne.1 .and. ((sync.lt.1.0) .or. (schk.lt.1.5))) cycle
 | 
				
			||||||
!           if(nqd.ne.1 .and. ((sync.lt.1.0) .or. (schk.lt.1.8))) cycle
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
           call timer('jt9fano ',0)
 | 
					           call timer('jt9fano ',0)
 | 
				
			||||||
           call jt9fano(i1SoftSymbols,limit,nlim,msg)
 | 
					           call jt9fano(i1SoftSymbols,limit,nlim,msg)
 | 
				
			||||||
@ -117,14 +116,18 @@ subroutine decjt9(ss,id2,nutc,nfqso,newdat,npts8,nfa,nfsplit,nfb,ntol,  &
 | 
				
			|||||||
              if(nqd.eq.0) ndecodes0=ndecodes0+1
 | 
					              if(nqd.eq.0) ndecodes0=ndecodes0+1
 | 
				
			||||||
              if(nqd.eq.1) ndecodes1=ndecodes1+1
 | 
					              if(nqd.eq.1) ndecodes1=ndecodes1+1
 | 
				
			||||||
 | 
					
 | 
				
			||||||
              !$omp critical(decode_results) ! serialize writes - see also jt65a.f90
 | 
					!$omp critical(decode_results) ! serialize writes - see also jt65a.f90
 | 
				
			||||||
              write(*,1000) nutc,nsnr,xdt,nint(freq),msg
 | 
					              write(*,1000) nutc,nsnr,xdt,nint(freq),msg
 | 
				
			||||||
1000          format(i4.4,i4,f5.1,i5,1x,'@',1x,a22)
 | 
					1000          format(i4.4,i4,f5.1,i5,1x,'@',1x,a22)
 | 
				
			||||||
 | 
					!              i1=index(infile,'.wav')
 | 
				
			||||||
 | 
					!              write(*,1000) infile(i1-11:i1-1),nsnr,xdt,nint(freq),msg,   &
 | 
				
			||||||
 | 
					!                   schk,drift,a3,nlim
 | 
				
			||||||
 | 
					!1000          format(a11,i4,f5.1,i5,1x,'@',1x,a22,3f6.1,i6)
 | 
				
			||||||
              write(13,1002) nutc,nsync,nsnr,xdt,freq,ndrift,msg
 | 
					              write(13,1002) nutc,nsync,nsnr,xdt,freq,ndrift,msg
 | 
				
			||||||
1002          format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a22,' JT9')
 | 
					1002          format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a22,' JT9')
 | 
				
			||||||
              call flush(6)
 | 
					              call flush(6)
 | 
				
			||||||
              call flush(13)
 | 
					              call flush(13)
 | 
				
			||||||
              !$omp end critical(decode_results)
 | 
					!$omp end critical(decode_results)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
              iaa=max(1,i-1)
 | 
					              iaa=max(1,i-1)
 | 
				
			||||||
              ibb=min(NSMAX,i+22)
 | 
					              ibb=min(NSMAX,i+22)
 | 
				
			||||||
 | 
				
			|||||||
@ -9,7 +9,7 @@ subroutine fano232(symbol,nbits,mettab,ndelta,maxcycles,dat,     &
 | 
				
			|||||||
  parameter (MAXBYTES=(MAXBITS+7)/8)
 | 
					  parameter (MAXBYTES=(MAXBITS+7)/8)
 | 
				
			||||||
  integer*1 symbol(0:2*MAXBITS-1)  !Soft symbols (as unsigned i*1)
 | 
					  integer*1 symbol(0:2*MAXBITS-1)  !Soft symbols (as unsigned i*1)
 | 
				
			||||||
  integer*1 dat(MAXBYTES)          !Decoded user data, 8 bits per byte
 | 
					  integer*1 dat(MAXBYTES)          !Decoded user data, 8 bits per byte
 | 
				
			||||||
  integer mettab(0:255,0:1)        !Metric table
 | 
					  integer mettab(-128:127,0:1)        !Metric table
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! These were the "node" structure in Karn's C code:
 | 
					! These were the "node" structure in Karn's C code:
 | 
				
			||||||
  integer nstate(0:MAXBITS-1)      !Encoder state of next node
 | 
					  integer nstate(0:MAXBITS-1)      !Encoder state of next node
 | 
				
			||||||
@ -31,8 +31,6 @@ subroutine fano232(symbol,nbits,mettab,ndelta,maxcycles,dat,     &
 | 
				
			|||||||
     j=2*np
 | 
					     j=2*np
 | 
				
			||||||
     i4a=symbol(j)
 | 
					     i4a=symbol(j)
 | 
				
			||||||
     i4b=symbol(j+1)
 | 
					     i4b=symbol(j+1)
 | 
				
			||||||
     if (i4a.lt.0) i4a=i4a+256
 | 
					 | 
				
			||||||
     if (i4b.lt.0) i4b=i4b+256
 | 
					 | 
				
			||||||
     metrics(0,np) = mettab(i4a,0) + mettab(i4b,0)
 | 
					     metrics(0,np) = mettab(i4a,0) + mettab(i4b,0)
 | 
				
			||||||
     metrics(1,np) = mettab(i4a,0) + mettab(i4b,1)
 | 
					     metrics(1,np) = mettab(i4a,0) + mettab(i4b,1)
 | 
				
			||||||
     metrics(2,np) = mettab(i4a,1) + mettab(i4b,0)
 | 
					     metrics(2,np) = mettab(i4a,1) + mettab(i4b,0)
 | 
				
			||||||
 | 
				
			|||||||
@ -31,6 +31,7 @@ subroutine fillcom(nutc0,ndepth0,nrxfreq,mode,tx9,flow,fsplit,fhigh)
 | 
				
			|||||||
    nmode=mode
 | 
					    nmode=mode
 | 
				
			||||||
  end if
 | 
					  end if
 | 
				
			||||||
  datetime="2013-Apr-16 15:13"
 | 
					  datetime="2013-Apr-16 15:13"
 | 
				
			||||||
  
 | 
					  if(mode.eq.9 .and. nfsplit.ne.2700) nfa=nfsplit
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  return
 | 
					  return
 | 
				
			||||||
end subroutine fillcom
 | 
					end subroutine fillcom
 | 
				
			||||||
 | 
				
			|||||||
@ -39,7 +39,7 @@ program jt9
 | 
				
			|||||||
       mousefqso,newdat,nfa,nfsplit,nfb,ntol,kin,nzhsym,nsynced,ndecoded
 | 
					       mousefqso,newdat,nfa,nfsplit,nfb,ntol,kin,nzhsym,nsynced,ndecoded
 | 
				
			||||||
  common/tracer/limtrace,lu
 | 
					  common/tracer/limtrace,lu
 | 
				
			||||||
  common/patience/npatience,nthreads
 | 
					  common/patience/npatience,nthreads
 | 
				
			||||||
  common/decstats/num65,numbm,numkv,num9,numfano
 | 
					  common/decstats/num65,numbm,numkv,num9,numfano,infile
 | 
				
			||||||
  data npatience/1/,nthreads/1/
 | 
					  data npatience/1/,nthreads/1/
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  do
 | 
					  do
 | 
				
			||||||
 | 
				
			|||||||
@ -14,7 +14,7 @@ subroutine jt9fano(i1SoftSymbols,limit,nlim,msg)
 | 
				
			|||||||
  real*4 xx0(0:255)
 | 
					  real*4 xx0(0:255)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  logical first
 | 
					  logical first
 | 
				
			||||||
  integer*4 mettab(0:255,0:1)
 | 
					  integer*4 mettab(-128:127,0:1)
 | 
				
			||||||
  data first/.true./
 | 
					  data first/.true./
 | 
				
			||||||
  data xx0/                                                      & !Metric table
 | 
					  data xx0/                                                      & !Metric table
 | 
				
			||||||
        1.000, 1.000, 1.000, 1.000, 1.000, 1.000, 1.000, 1.000,  &
 | 
					        1.000, 1.000, 1.000, 1.000, 1.000, 1.000, 1.000, 1.000,  &
 | 
				
			||||||
@ -54,17 +54,21 @@ subroutine jt9fano(i1SoftSymbols,limit,nlim,msg)
 | 
				
			|||||||
  if(first) then
 | 
					  if(first) then
 | 
				
			||||||
! Get the metric table
 | 
					! Get the metric table
 | 
				
			||||||
     bias=0.5
 | 
					     bias=0.5
 | 
				
			||||||
     scale=10
 | 
					     scale=50
 | 
				
			||||||
 | 
					     ndelta=nint(3.4*scale)
 | 
				
			||||||
 | 
					     ib=160                          !Break point
 | 
				
			||||||
 | 
					     slope=2                         !Slope beyond break
 | 
				
			||||||
     do i=0,255
 | 
					     do i=0,255
 | 
				
			||||||
        mettab(i,0)=nint(scale*(xx0(i)-bias))
 | 
					        mettab(i-128,0)=nint(scale*(xx0(i)-bias))
 | 
				
			||||||
        if(i.ge.1) mettab(256-i,1)=mettab(i,0)
 | 
					        if(i.gt.ib) mettab(i-128,0)=mettab(ib-128,0) - slope*(i-ib)
 | 
				
			||||||
 | 
					        if(i.ge.1) mettab(128-i,1)=mettab(i-128,0)
 | 
				
			||||||
     enddo
 | 
					     enddo
 | 
				
			||||||
 | 
					     mettab(-128,1)=mettab(-127,1)
 | 
				
			||||||
     first=.false.
 | 
					     first=.false.
 | 
				
			||||||
  endif
 | 
					  endif
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  msg='                      '
 | 
					  msg='                      '
 | 
				
			||||||
  nbits=72
 | 
					  nbits=72
 | 
				
			||||||
  ndelta=17
 | 
					 | 
				
			||||||
  call fano232(i1SoftSymbols,nbits+31,mettab,ndelta,limit,i1DecodedBytes,   &
 | 
					  call fano232(i1SoftSymbols,nbits+31,mettab,ndelta,limit,i1DecodedBytes,   &
 | 
				
			||||||
       ncycles,metric,ierr)
 | 
					       ncycles,metric,ierr)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
@ -1,5 +1,5 @@
 | 
				
			|||||||
subroutine softsym(id2,npts8,nsps8,newdat,fpk,syncpk,snrdb,xdt,        &
 | 
					subroutine softsym(id2,npts8,nsps8,newdat,fpk,syncpk,snrdb,xdt,        &
 | 
				
			||||||
     freq,drift,schk,i1SoftSymbols)
 | 
					     freq,drift,a3,schk,i1SoftSymbols)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! Compute the soft symbols
 | 
					! Compute the soft symbols
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -28,6 +28,8 @@ subroutine softsym(id2,npts8,nsps8,newdat,fpk,syncpk,snrdb,xdt,        &
 | 
				
			|||||||
  call timer('afc9    ',1)
 | 
					  call timer('afc9    ',1)
 | 
				
			||||||
  freq=fpk - a(1)
 | 
					  freq=fpk - a(1)
 | 
				
			||||||
  drift=-2.0*a(2)
 | 
					  drift=-2.0*a(2)
 | 
				
			||||||
 | 
					  a3=a(3)
 | 
				
			||||||
 | 
					  a(3)=0.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  call timer('twkfreq ',0)
 | 
					  call timer('twkfreq ',0)
 | 
				
			||||||
  call twkfreq(c3,c5,nz3,fsample,a)   !Correct for delta f, f1, f2 ==> a(1:3)
 | 
					  call twkfreq(c3,c5,nz3,fsample,a)   !Correct for delta f, f1, f2 ==> a(1:3)
 | 
				
			||||||
 | 
				
			|||||||
@ -77,9 +77,10 @@ subroutine symspec2(c5,nz3,nsps8,nspsd,fsample,freq,drift,snrdb,schk,    &
 | 
				
			|||||||
        i4=nint(scale*(r1-r0))
 | 
					        i4=nint(scale*(r1-r0))
 | 
				
			||||||
        if(i4.lt.-127) i4=-127
 | 
					        if(i4.lt.-127) i4=-127
 | 
				
			||||||
        if(i4.gt.127) i4=127
 | 
					        if(i4.gt.127) i4=127
 | 
				
			||||||
        i4=i4+128
 | 
					!        i4=i4+128
 | 
				
			||||||
        if(i4.le.127) i1SoftSymbolsScrambled(k)=i4
 | 
					!        if(i4.le.127) i1SoftSymbolsScrambled(k)=i4
 | 
				
			||||||
        if(i4.ge.128) i1SoftSymbolsScrambled(k)=i4-256
 | 
					!        if(i4.ge.128) i1SoftSymbolsScrambled(k)=i4-256
 | 
				
			||||||
 | 
					        i1SoftSymbolsScrambled(k)=i4
 | 
				
			||||||
     enddo
 | 
					     enddo
 | 
				
			||||||
  enddo
 | 
					  enddo
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
@ -13,13 +13,11 @@ subroutine twkfreq(c3,c4,npts,fsample,a)
 | 
				
			|||||||
  s=2.0/npts
 | 
					  s=2.0/npts
 | 
				
			||||||
  do i=1,npts
 | 
					  do i=1,npts
 | 
				
			||||||
     x=s*(i-x0)
 | 
					     x=s*(i-x0)
 | 
				
			||||||
     if(mod(i,100).eq.1) then
 | 
					     p2=1.5*x*x - 0.5
 | 
				
			||||||
        p2=1.5*x*x - 0.5
 | 
					 | 
				
			||||||
!          p3=2.5*(x**3) - 1.5*x
 | 
					!          p3=2.5*(x**3) - 1.5*x
 | 
				
			||||||
!          p4=4.375*(x**4) - 3.75*(x**2) + 0.375
 | 
					!          p4=4.375*(x**4) - 3.75*(x**2) + 0.375
 | 
				
			||||||
        dphi=(a(1) + x*a(2) + p2*a(3)) * (twopi/fsample)
 | 
					     dphi=(a(1) + x*a(2) + p2*a(3)) * (twopi/fsample)
 | 
				
			||||||
        wstep=cmplx(cos(dphi),sin(dphi))
 | 
					     wstep=cmplx(cos(dphi),sin(dphi))
 | 
				
			||||||
     endif
 | 
					 | 
				
			||||||
     w=w*wstep
 | 
					     w=w*wstep
 | 
				
			||||||
     c4(i)=w*c3(i)
 | 
					     c4(i)=w*c3(i)
 | 
				
			||||||
  enddo
 | 
					  enddo
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user