mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2024-11-08 18:16:02 -05:00
ffdeafe3bb
This change introduces the program jt9_omp which is a testbed for a multi-threaded version of the jt9 decoder program. The program jt9_omp should be a directly substitutable for jt9 except that JT65 and JT9 decodes are computed in parallel. Also enable the OpenMP directives in decoder.f90 - note this is not yet a working multi-threaded decoder and the existing jt9 is still the correct decoder to be used in WSJT-X. Increased the available stack size for jt9_omp.exe as this is a hard limit on Windows and the default is not big enough for the OpenMP version of jt9. Also Fortran array bounds checking is now disabled for Release configuration builds so as to improve performance a little. git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@4922 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
85 lines
2.0 KiB
Fortran
85 lines
2.0 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 timer('jt65a ',0)
|
|
call jt65a(dd,npts65,newdat,nutc,nf1,nf2,nfqso,ntol65,nagain,ndecoded)
|
|
call timer('jt65a ',1)
|
|
done65=.true.
|
|
endif
|
|
|
|
if(nmode.eq.65) go to 800
|
|
|
|
! print*,'A'
|
|
!$OMP PARALLEL SECTIONS PRIVATE(id)
|
|
|
|
!$OMP SECTION
|
|
! print*,'B'
|
|
call timer('decjt9 ',0)
|
|
call decjt9(ss,id2,nutc,nfqso,newdat,npts8,nfa,nfsplit,nfb,ntol,nzhsym, &
|
|
nagain,ndepth,nmode)
|
|
call timer('decjt9 ',1)
|
|
|
|
!$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 timer('jt65a ',0)
|
|
call jt65a(dd,npts65,newdat,nutc,nf1,nf2,nfqso,ntol65,nagain,ndecoded)
|
|
call timer('jt65a ',1)
|
|
endif
|
|
|
|
!$OMP END PARALLEL SECTIONS
|
|
! 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
|