WSJT-X/lib/decoder.f90
Bill Somerville 1271243952 Thread safe lib/timer.f90
Accounts for each traced call per thread and accumulates by rolling up
calls with an identical call chain before printing the statistics. The
print now accounts for function calls  in their call chain so the same
function will be reported more than  once if it is called in different
places.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@4937 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
2015-02-05 22:07:19 +00:00

91 lines
2.4 KiB
Fortran

subroutine decoder(ss,id2)
use prog_args
!$ use omp_lib
include 'constants.f90'
real ss(184,NSMAX)
character*20 datetime
logical 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
integer onlevel(0:10)
common/tracer_priv/level,onlevel
!$omp threadprivate(/tracer_priv/)
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
!$ call omp_set_dynamic(.true.)
!$omp parallel sections num_threads(2) copyin(/tracer_priv/)
!$omp section
if(nmode.eq.65 .or. (nmode.gt.65 .and. ntxmode.eq.65)) then
! We're decoding JT65 or 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)
else
! We're decoding JT9 or should do this mode first
call timer('decjt9 ',0)
call decjt9(ss,id2,nutc,nfqso,newdat,npts8,nfa,nfsplit,nfb,ntol,nzhsym, &
nagain,ndepth,nmode)
call timer('decjt9 ',1)
endif
!$omp section
if(nmode.gt.65) then ! do the other mode in dual mode
if (ntxmode.eq.9) then
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)
else
call timer('decjt9 ',0)
call decjt9(ss,id2,nutc,nfqso,newdat,npts8,nfa,nfsplit,nfb,ntol,nzhsym, &
nagain,ndepth,nmode)
call timer('decjt9 ',1)
end if
endif
!$omp end parallel sections
! 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