2014-04-19 22:44:47 -04:00
|
|
|
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
|
2014-12-02 19:06:54 -05:00
|
|
|
open(13,file=trim(temp_dir)//'/decoded.txt',status='unknown')
|
2014-04-19 22:44:47 -04:00
|
|
|
else
|
2015-02-01 11:23:36 -05:00
|
|
|
open(13,file=trim(temp_dir)//'/decoded.txt',status='unknown', &
|
|
|
|
position='append')
|
2014-04-19 22:44:47 -04:00
|
|
|
end if
|
2015-02-01 11:23:36 -05:00
|
|
|
open(22,file=trim(temp_dir)//'/kvasd.dat',access='direct',recl=1024, &
|
|
|
|
status='unknown')
|
2014-04-19 22:44:47 -04:00
|
|
|
|
|
|
|
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
|
2014-07-09 08:58:12 -04:00
|
|
|
! We're decoding JT65, and should do this mode first
|
2014-04-19 22:44:47 -04:00
|
|
|
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
|
|
|
|
|
2015-02-01 11:23:36 -05:00
|
|
|
! print*,'A'
|
|
|
|
!!$OMP PARALLEL PRIVATE(id)
|
|
|
|
!!$OMP SECTIONS
|
2014-04-19 22:44:47 -04:00
|
|
|
|
2015-02-01 11:23:36 -05:00
|
|
|
!!$OMP SECTION
|
|
|
|
! print*,'B'
|
|
|
|
call decjt9(ss,id2,nutc,nfqso,newdat,npts8,nfa,nfsplit,nfb,ntol,nzhsym, &
|
|
|
|
nagain,ndepth,nmode)
|
2014-04-19 22:44:47 -04:00
|
|
|
|
2015-02-01 11:23:36 -05:00
|
|
|
!!$OMP SECTION
|
2014-04-19 22:44:47 -04:00
|
|
|
if(nmode.ge.65 .and. (.not.done65)) then
|
|
|
|
if(newdat.ne.0) dd(1:npts65)=id2(1:npts65)
|
|
|
|
nf1=nfa
|
|
|
|
nf2=nfb
|
2015-02-01 11:23:36 -05:00
|
|
|
! print*,'C'
|
2014-04-19 22:44:47 -04:00
|
|
|
call jt65a(dd,npts65,newdat,nutc,nf1,nf2,nfqso,ntol65,nagain,ndecoded)
|
|
|
|
endif
|
|
|
|
|
2015-02-01 11:23:36 -05:00
|
|
|
!!$OMP END SECTIONS NOWAIT
|
|
|
|
!!$OMP END PARALLEL
|
|
|
|
! print*,'D'
|
|
|
|
|
2014-10-30 15:29:16 -04:00
|
|
|
! JT65 is not yet producing info for nsynced, ndecoded.
|
2014-04-19 22:44:47 -04:00
|
|
|
800 write(*,1010) nsynced,ndecoded
|
|
|
|
1010 format('<DecodeFinished>',2i4)
|
|
|
|
call flush(6)
|
|
|
|
close(13)
|
|
|
|
close(22)
|
|
|
|
|
|
|
|
return
|
|
|
|
end subroutine decoder
|