2015-11-17 20:28:12 -05:00
|
|
|
subroutine decode65a(dd,npts,newdat,nqd,f0,nflip,mode65,ntrials, &
|
2016-05-03 16:30:49 -04:00
|
|
|
naggressive,ndepth,ntol,mycall,hiscall,hisgrid,nexp_decode, &
|
2016-05-04 14:16:09 -04:00
|
|
|
single_decode,sync2,a,dt,nft,nspecial,qual,nhist,nsmo,decoded)
|
2013-07-08 09:17:22 -04:00
|
|
|
|
|
|
|
! Apply AFC corrections to a candidate JT65 signal, then decode it.
|
|
|
|
|
2016-03-10 09:25:22 -05:00
|
|
|
use jt65_mod
|
2015-12-27 10:40:57 -05:00
|
|
|
use timer_module, only: timer
|
|
|
|
|
2013-07-08 09:17:22 -04:00
|
|
|
parameter (NMAX=60*12000) !Samples per 60 s
|
|
|
|
real*4 dd(NMAX) !92 MB: raw data from Linrad timf2
|
2016-03-02 14:44:09 -05:00
|
|
|
complex cx(NMAX/8) !Data at 1378.125 sps
|
|
|
|
complex cx1(NMAX/8) !Data at 1378.125 sps, offset by 355.3 Hz
|
2013-07-08 09:17:22 -04:00
|
|
|
complex c5x(NMAX/32) !Data at 344.53125 Hz
|
|
|
|
complex c5a(512)
|
|
|
|
real s2(66,126)
|
|
|
|
real a(5)
|
2016-05-03 16:30:49 -04:00
|
|
|
logical single_decode,first
|
2016-03-08 10:45:15 -05:00
|
|
|
character decoded*22,decoded_best*22
|
2015-12-16 14:31:12 -05:00
|
|
|
character mycall*12,hiscall*12,hisgrid*6
|
2013-07-08 09:17:22 -04:00
|
|
|
data first/.true./,jjjmin/1000/,jjjmax/-1000/
|
|
|
|
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)
|
2016-03-02 14:44:09 -05:00
|
|
|
if(mode65.eq.4) call filbig(dd,npts,f0+355.297852,newdat,cx1,n5,sq0)
|
2013-07-08 09:17:22 -04:00
|
|
|
call timer('filbig ',1)
|
|
|
|
! NB: cx has sample rate 12000*77125/672000 = 1378.125 Hz
|
|
|
|
|
2016-05-03 16:30:49 -04:00
|
|
|
! Check for a shorthand message
|
|
|
|
if(single_decode) then
|
2016-05-04 14:16:09 -04:00
|
|
|
call sh65(cx,n5,mode65,ntol,xdf,nspecial,sync2)
|
2016-05-03 16:30:49 -04:00
|
|
|
if(nspecial.gt.0) then
|
|
|
|
a=0.
|
|
|
|
a(1)=xdf
|
|
|
|
nflip=0
|
|
|
|
endif
|
|
|
|
endif
|
2016-05-04 14:44:05 -04:00
|
|
|
if(nflip.eq.0) go to 900
|
2016-05-03 16:30:49 -04:00
|
|
|
|
2015-11-17 20:28:12 -05:00
|
|
|
! Find best DF, drift, curvature, and DT. Start by downsampling to 344.53125 Hz
|
2013-07-08 09:17:22 -04:00
|
|
|
call timer('fil6521 ',0)
|
2015-11-17 20:28:12 -05:00
|
|
|
call fil6521(cx,n5,c5x,n6)
|
2013-07-08 09:17:22 -04:00
|
|
|
call timer('fil6521 ',1)
|
|
|
|
|
|
|
|
fsample=1378.125/4.
|
|
|
|
|
|
|
|
call timer('afc65b ',0)
|
2015-11-17 20:28:12 -05:00
|
|
|
! 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)
|
2013-07-08 09:17:22 -04:00
|
|
|
call timer('afc65b ',1)
|
2016-03-25 14:02:57 -04:00
|
|
|
dtbest=dtbest+0.003628 !Remove decimation filter and coh. integrator delay
|
|
|
|
dt=dtbest !Return new, improved estimate of dt
|
2013-07-08 09:17:22 -04:00
|
|
|
sync2=3.7e-4*ccfbest/sq0 !Constant is empirical
|
2016-03-02 14:44:09 -05:00
|
|
|
if(mode65.eq.4) cx=cx1
|
2013-07-08 09:17:22 -04:00
|
|
|
|
|
|
|
! 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.
|
2015-11-17 20:28:12 -05:00
|
|
|
a(3)=0
|
2013-07-08 09:17:22 -04:00
|
|
|
call timer('twkfreq ',0)
|
|
|
|
call twkfreq65(cx,n5,a)
|
|
|
|
call timer('twkfreq ',1)
|
|
|
|
|
2015-11-17 20:28:12 -05:00
|
|
|
! Compute spectrum for each symbol.
|
2013-07-08 09:17:22 -04:00
|
|
|
nsym=126
|
|
|
|
nfft=512
|
2016-03-02 15:14:17 -05:00
|
|
|
df=1378.125/nfft
|
2015-11-17 20:28:12 -05:00
|
|
|
j=int(dtbest*1378.125)
|
2013-07-08 09:17:22 -04:00
|
|
|
|
|
|
|
call timer('sh_ffts ',0)
|
2016-03-07 15:00:23 -05:00
|
|
|
c5a=cmplx(0.0,0.0)
|
2013-07-08 09:17:22 -04:00
|
|
|
do k=1,nsym
|
|
|
|
do i=1,nfft
|
|
|
|
j=j+1
|
2015-11-25 11:40:22 -05:00
|
|
|
if(j.ge.1 .and. j.le.NMAX/8) then
|
|
|
|
c5a(i)=cx(j)
|
|
|
|
else
|
|
|
|
c5a(i)=0.
|
|
|
|
endif
|
2013-07-08 09:17:22 -04:00
|
|
|
enddo
|
|
|
|
call four2a(c5a,nfft,1,1,1)
|
2016-03-07 15:00:23 -05:00
|
|
|
do i=1,512
|
|
|
|
jj=i
|
|
|
|
if(i.gt.256) jj=i-512
|
|
|
|
s1(jj,k)=real(c5a(i))**2 + aimag(c5a(i))**2
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
call timer('sh_ffts ',1)
|
|
|
|
|
|
|
|
call timer('dec65b ',0)
|
2016-03-08 10:45:15 -05:00
|
|
|
qualbest=0.
|
2016-03-25 14:02:57 -04:00
|
|
|
qual0=-1.e30
|
2016-03-19 08:41:53 -04:00
|
|
|
minsmo=0
|
2016-03-07 15:00:23 -05:00
|
|
|
maxsmo=0
|
2016-03-19 08:41:53 -04:00
|
|
|
if(mode65.ge.2) then
|
|
|
|
minsmo=nint(width/df)
|
|
|
|
maxsmo=2*minsmo
|
|
|
|
endif
|
2016-03-08 10:45:15 -05:00
|
|
|
nn=0
|
2016-03-19 08:41:53 -04:00
|
|
|
do ismo=minsmo,maxsmo
|
2016-03-07 15:00:23 -05:00
|
|
|
if(ismo.gt.0) then
|
|
|
|
do j=1,126
|
2016-03-19 08:41:53 -04:00
|
|
|
call smo121(s1(-255,j),512)
|
|
|
|
if(j.eq.1) nn=nn+1
|
|
|
|
if(nn.ge.4) then
|
|
|
|
call smo121(s1(-255,j),512)
|
|
|
|
if(j.eq.1) nn=nn+1
|
|
|
|
endif
|
2016-03-07 15:00:23 -05:00
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
|
2013-07-08 09:17:22 -04:00
|
|
|
do i=1,66
|
|
|
|
jj=i
|
|
|
|
if(mode65.eq.2) jj=2*i-1
|
2016-03-02 14:44:09 -05:00
|
|
|
if(mode65.eq.4) then
|
|
|
|
ff=4*(i-1)*df - 355.297852
|
|
|
|
jj=nint(ff/df)+1
|
|
|
|
endif
|
2016-03-07 15:00:23 -05:00
|
|
|
s2(i,1:126)=s1(jj,1:126)
|
2013-07-08 09:17:22 -04:00
|
|
|
enddo
|
2016-03-07 15:00:23 -05:00
|
|
|
|
2016-03-25 14:02:57 -04:00
|
|
|
nadd=ismo !### ??? ###
|
|
|
|
call decode65b(s2,nflip,nadd,mode65,ntrials,naggressive,ndepth, &
|
2016-03-07 15:00:23 -05:00
|
|
|
mycall,hiscall,hisgrid,nexp_decode,nqd,nft,qual,nhist,decoded)
|
2016-03-11 11:26:06 -05:00
|
|
|
|
2016-03-07 15:00:23 -05:00
|
|
|
if(nft.eq.1) then
|
|
|
|
nsmo=ismo
|
2016-03-11 11:26:06 -05:00
|
|
|
param(9)=nsmo
|
|
|
|
nsum=1
|
2016-03-07 15:00:23 -05:00
|
|
|
exit
|
2016-03-07 15:54:12 -05:00
|
|
|
else if(nft.eq.2) then
|
2016-03-08 10:45:15 -05:00
|
|
|
if(qual.gt.qualbest) then
|
|
|
|
decoded_best=decoded
|
|
|
|
qualbest=qual
|
|
|
|
nnbest=nn
|
|
|
|
nsmobest=ismo
|
|
|
|
endif
|
2016-03-07 15:00:23 -05:00
|
|
|
endif
|
2016-03-25 14:02:57 -04:00
|
|
|
if(qual.lt.qual0) exit
|
|
|
|
qual0=qual
|
2013-07-08 09:17:22 -04:00
|
|
|
enddo
|
|
|
|
|
2016-03-08 10:45:15 -05:00
|
|
|
if(nft.eq.2) then
|
|
|
|
decoded=decoded_best
|
|
|
|
qual=qualbest
|
|
|
|
nsmo=nsmobest
|
2016-03-10 15:29:00 -05:00
|
|
|
param(9)=nsmo
|
2016-03-25 14:02:57 -04:00
|
|
|
nn=nnbest
|
2016-03-08 10:45:15 -05:00
|
|
|
endif
|
|
|
|
|
2013-07-08 09:17:22 -04:00
|
|
|
call timer('dec65b ',1)
|
|
|
|
|
2016-05-03 16:30:49 -04:00
|
|
|
900 return
|
2013-07-08 09:17:22 -04:00
|
|
|
end subroutine decode65a
|