WSJT-X/lib/decoder.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

81 lines
1.8 KiB
Fortran

subroutine decoder(ss,id2)
use prog_args
include 'constants.f90'
real ss(184,NSMAX)
character*20 datetime
logical done65,baddata
integer*2 id2(NTMAX*12000)
real*4 dd(NTMAX*12000)
common/npar/nutc,ndiskdat,ntrperiod,nfqso,newdat,npts8,nfa,nfsplit,nfb, &
ntol,kin,nzhsym,nsave,nagain,ndepth,ntxmode,nmode,datetime
common/tracer/limtrace,lu
save
nfreqs0=0
nfreqs1=0
ndecodes0=0
ndecodes1=0
if (nagain .eq. 0) then
open(13,file=trim(temp_dir)//'/decoded.txt',status='unknown')
else
open(13,file=trim(temp_dir)//'/decoded.txt',status='unknown', &
position='append')
end if
open(22,file=trim(temp_dir)//'/kvasd.dat',access='direct',recl=1024, &
status='unknown')
npts65=52*12000
if(baddata(id2,npts65)) then
nsynced=0
ndecoded=0
go to 800
endif
ntol65=20
done65=.false.
if((nmode.eq.65 .or. nmode.eq.65+9) .and. ntxmode.eq.65) then
! We're decoding JT65, and should do this mode first
if(newdat.ne.0) dd(1:npts65)=id2(1:npts65)
nf1=nfa
nf2=nfb
call jt65a(dd,npts65,newdat,nutc,nf1,nf2,nfqso,ntol65,nagain,ndecoded)
done65=.true.
endif
if(nmode.eq.65) go to 800
! print*,'A'
!!$OMP PARALLEL PRIVATE(id)
!!$OMP SECTIONS
!!$OMP SECTION
! print*,'B'
call decjt9(ss,id2,nutc,nfqso,newdat,npts8,nfa,nfsplit,nfb,ntol,nzhsym, &
nagain,ndepth,nmode)
!!$OMP SECTION
if(nmode.ge.65 .and. (.not.done65)) then
if(newdat.ne.0) dd(1:npts65)=id2(1:npts65)
nf1=nfa
nf2=nfb
! print*,'C'
call jt65a(dd,npts65,newdat,nutc,nf1,nf2,nfqso,ntol65,nagain,ndecoded)
endif
!!$OMP END SECTIONS NOWAIT
!!$OMP END PARALLEL
! print*,'D'
! JT65 is not yet producing info for nsynced, ndecoded.
800 write(*,1010) nsynced,ndecoded
1010 format('<DecodeFinished>',2i4)
call flush(6)
close(13)
close(22)
return
end subroutine decoder