WSJT-X/lib/decode65a.f90
Bill Somerville f416a52def Make Fortran profiling timer function a callback with a default null implementation
Groundwork for calling the decoders directly from C/C++ threads.

To  access   the  timer   module  timer_module   must  now   be  used.
Instrumented code need  only use the module function  'timer' which is
now a  procedure pointer that  is guaranteed to be  associated (unless
null()  is assigned  to it,  which should  not be  done). The  default
behaviour of 'timer' is to do nothing.

If a  Fortran program  wishes to  profile code it  should now  use the
timer_impl module  which contains a default  timer implementation. The
main program should call 'init_timer([filename])' before using 'timer'
or     calling     routines     that     are     instrumented.      If
'init_timer([filename])'.  If it is called  then an optional file name
may  be  provided  with  'timer.out'  being used  as  a  default.  The
procedure 'fini_timer()' may be called to close the file.

The default  timer implementation is  thread safe if used  with OpenMP
multi-threaded code  so long as  the OpenMP  thread team is  given the
copyin(/timer_private/) attribute  for correct operation.   The common
block /timer_private/ should  be included for OpenMP  use by including
the file 'timer_common.inc'.

The module 'lib/timer_C_wrapper.f90' provides  a Fortran wrapper along
with 'init' and 'fini' subroutines  which allow a C/C++ application to
call timer instrumented  Fortran code and for it  to receive callbacks
of 'timer()' subroutine invocations.  No C/C++ timer implementation is
provided at this stage.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@6320 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
2015-12-27 15:40:57 +00:00

87 lines
2.5 KiB
Fortran

subroutine decode65a(dd,npts,newdat,nqd,f0,nflip,mode65,ntrials, &
naggressive,ndepth,mycall,hiscall,hisgrid,nexp_decode,sync2, &
a,dt,nft,qual,nhist,decoded)
! Apply AFC corrections to a candidate JT65 signal, then decode it.
use timer_module, only: timer
parameter (NMAX=60*12000) !Samples per 60 s
real*4 dd(NMAX) !92 MB: raw data from Linrad timf2
complex cx(NMAX/8) !Data at 1378.125 samples/s
complex c5x(NMAX/32) !Data at 344.53125 Hz
complex c5a(512)
real s2(66,126)
real a(5)
logical first
character decoded*22
character mycall*12,hiscall*12,hisgrid*6
data first/.true./,jjjmin/1000/,jjjmax/-1000/
data nhz0/-9999999/
save
! Mix sync tone to baseband, low-pass filter, downsample to 1378.125 Hz
call timer('filbig ',0)
call filbig(dd,npts,f0,newdat,cx,n5,sq0)
call timer('filbig ',1)
! NB: cx has sample rate 12000*77125/672000 = 1378.125 Hz
! Find best DF, drift, curvature, and DT. Start by downsampling to 344.53125 Hz
call timer('fil6521 ',0)
call fil6521(cx,n5,c5x,n6)
call timer('fil6521 ',1)
fsample=1378.125/4.
call timer('afc65b ',0)
! Best fit for DF, drift, banana-coefficient, and dt. fsample = 344.53125 S/s
dtbest=dt
call afc65b(c5x,n6,fsample,nflip,a,ccfbest,dtbest)
call timer('afc65b ',1)
sync2=3.7e-4*ccfbest/sq0 !Constant is empirical
! Apply AFC corrections to the time-domain signal
! Now we are back to using the 1378.125 Hz sample rate, enough to
! accommodate the full JT65C bandwidth.
a(3)=0
call timer('twkfreq ',0)
call twkfreq65(cx,n5,a)
call timer('twkfreq ',1)
! Compute spectrum for each symbol.
nsym=126
nfft=512
j=int(dtbest*1378.125)
c5a=cmplx(0.0,0.0)
call timer('sh_ffts ',0)
do k=1,nsym
do i=1,nfft
j=j+1
if(j.ge.1 .and. j.le.NMAX/8) then
c5a(i)=cx(j)
else
c5a(i)=0.
endif
enddo
call four2a(c5a,nfft,1,1,1)
do i=1,66
jj=i
if(mode65.eq.2) jj=2*i-1
if(mode65.eq.4) jj=4*i-3
s2(i,k)=real(c5a(jj))**2 + aimag(c5a(jj))**2
enddo
enddo
call timer('sh_ffts ',1)
call timer('dec65b ',0)
call decode65b(s2,nflip,mode65,ntrials,naggressive,ndepth, &
mycall,hiscall,hisgrid,nexp_decode,nqd,nft,qual,nhist,decoded)
dt=dtbest !return new, improved estimate of dt
call timer('dec65b ',1)
return
end subroutine decode65a