WSJT-X/lib/downsam9.f90
Joe Taylor 94472ac31c Many changes in program jt9[.exe] aimed at speeding up the decoders.
The long FFTs can now use the multi-threaded FFTW routines.
Subroutine decode9.f90 was renamed jt9fano.f90.
The JT9 decoder's top-level functions were removed from decoder.f90
and put into a separate subroutine decjt90.f90.
Subroutine decoder.f90 is now configured for possible use of OpenMP 
SECTIONS, with the JT9 and JT65 decoders running concurrently on
a multi-core machine.  Note, however, that this concurrent processing 
is not yet fully implemented.  Probably calls to timer need to be removed; 
some variables used in calls to jt65a and decjt9 may need to be 
declared PRIVATE in decoder; some sections probably need to be declared 
CRITICAL; probably some SAVE statements in downstream routines have
made them not thread-safe; etc., etc.  

I'm a neophyte at using OpenMP.  Comments, suggestions, and/or tests by
others will be welcome!



git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@4919 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
2015-02-01 16:23:36 +00:00

93 lines
2.4 KiB
Fortran

subroutine downsam9(id2,npts8,nsps8,newdat,nspsd,fpk,c2,nz2)
!Downsample from id2() into C2() so as to yield nspsd samples per symbol,
!mixing from fpk down to zero frequency.
use, intrinsic :: iso_c_binding
use FFTW3
include 'constants.f90'
! parameter (NMAX1=1024*1920)
parameter (NMAX1=884736)
type(C_PTR) :: plan !Pointers plan for big FFT
integer*2 id2(0:8*npts8-1)
real*4 x1(0:NMAX1-1)
complex c1(0:NMAX1/2)
complex c2(0:4096-1)
real s(5000)
logical first
common/patience/npatience,nthreads
data first/.true./
save plan,first
nfft1=1024*nsps8 !Forward FFT length
df1=12000.0/nfft1
npts=8*npts8
if(newdat.eq.1) then
fac=6.963e-6 !Why this weird constant?
do i=0,npts-1
x1(i)=fac*id2(i)
enddo
x1(npts:nfft1-1)=0. !Zero the rest of x1
endif
if(first) then
nflags=FFTW_ESTIMATE
if(npatience.eq.1) nflags=FFTW_ESTIMATE_PATIENT
if(npatience.eq.2) nflags=FFTW_MEASURE
if(npatience.eq.3) nflags=FFTW_PATIENT
if(npatience.eq.4) nflags=FFTW_EXHAUSTIVE
! Plan the FFTs just once
plan=fftwf_plan_dft_r2c_1d(nfft1,x1,c1,nflags)
first=.false.
endif
if(newdat.eq.1) then
fac=6.963e-6 !Why this weird constant?
do i=0,npts-1
x1(i)=fac*id2(i)
enddo
x1(npts:nfft1-1)=0. !Zero the rest of x1
call timer('FFTbig9 ',0)
call fftwf_execute_dft_r2c(plan,x1,c1)
call timer('FFTbig9 ',1)
nadd=int(1.0/df1)
s=0.
do i=1,5000
j=int((i-1)/df1)
do n=1,nadd
j=j+1
s(i)=s(i)+real(c1(j))**2 + aimag(c1(j))**2
enddo
enddo
endif
ndown=8*nsps8/nspsd !Downsample factor
nfft2=nfft1/ndown !Backward FFT length
nh2=nfft2/2
nf=nint(fpk)
i0=int(fpk/df1)
nw=100
ia=max(1,nf-nw)
ib=min(5000,nf+nw)
call timer('pctile_1',0)
call pctile(s(ia),ib-ia+1,40,avenoise)
call timer('pctile_1',1)
fac=sqrt(1.0/avenoise)
do i=0,nfft2-1
j=i0+i
if(i.gt.nh2) j=j-nfft2
c2(i)=fac*c1(j)
enddo
call timer('FFTsmal9',0)
call four2a(c2,nfft2,1,1,1) !FFT back to time domain
call timer('FFTsmal9',1)
nz2=8*npts8/ndown
return
end subroutine downsam9