mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2024-11-25 21:58:38 -05:00
Add options for sub-symbol integration for sync and symbol estimation.
This commit is contained in:
parent
f17a07953e
commit
c176572ec0
@ -604,6 +604,7 @@ set (wsjt_FSRCS
|
|||||||
lib/fst240/gen_fst240wave.f90
|
lib/fst240/gen_fst240wave.f90
|
||||||
lib/fst240/genfst240.f90
|
lib/fst240/genfst240.f90
|
||||||
lib/fst240/get_fst240_bitmetrics.f90
|
lib/fst240/get_fst240_bitmetrics.f90
|
||||||
|
lib/fst240/get_fst240_bitmetrics2.f90
|
||||||
lib/fst240/ldpcsim240_101.f90
|
lib/fst240/ldpcsim240_101.f90
|
||||||
lib/fst240/ldpcsim240_74.f90
|
lib/fst240/ldpcsim240_74.f90
|
||||||
lib/fst240/osd240_101.f90
|
lib/fst240/osd240_101.f90
|
||||||
|
@ -1,4 +1,4 @@
|
|||||||
subroutine get_fst240_bitmetrics(cd,nss,hmod,nmax,bitmetrics,s4,badsync)
|
subroutine get_fst240_bitmetrics(cd,nss,hmod,nmax,nhicoh,bitmetrics,s4,badsync)
|
||||||
|
|
||||||
include 'fst240_params.f90'
|
include 'fst240_params.f90'
|
||||||
complex cd(0:NN*nss-1)
|
complex cd(0:NN*nss-1)
|
||||||
@ -87,10 +87,13 @@ subroutine get_fst240_bitmetrics(cd,nss,hmod,nmax,bitmetrics,s4,badsync)
|
|||||||
do nseq=1,nmax !Try coherent sequences of 1, 2, and 4 symbols
|
do nseq=1,nmax !Try coherent sequences of 1, 2, and 4 symbols
|
||||||
if(nseq.eq.1) nsym=1
|
if(nseq.eq.1) nsym=1
|
||||||
if(nseq.eq.2) nsym=2
|
if(nseq.eq.2) nsym=2
|
||||||
if(nseq.eq.3) nsym=3
|
if(nhicoh.eq.0) then
|
||||||
if(nseq.eq.4) nsym=4
|
if(nseq.eq.3) nsym=3
|
||||||
! if(nseq.eq.3) nsym=4
|
if(nseq.eq.4) nsym=4
|
||||||
! if(nseq.eq.4) nsym=8
|
else
|
||||||
|
if(nseq.eq.3) nsym=4
|
||||||
|
if(nseq.eq.4) nsym=8
|
||||||
|
endif
|
||||||
nt=4**nsym
|
nt=4**nsym
|
||||||
do ks=1,NN-nsym+1,nsym
|
do ks=1,NN-nsym+1,nsym
|
||||||
s2=0
|
s2=0
|
||||||
|
131
lib/fst240/get_fst240_bitmetrics2.f90
Normal file
131
lib/fst240/get_fst240_bitmetrics2.f90
Normal file
@ -0,0 +1,131 @@
|
|||||||
|
subroutine get_fst240_bitmetrics2(cd,nss,hmod,nsizes,bitmetrics,s4hmod,badsync)
|
||||||
|
|
||||||
|
include 'fst240_params.f90'
|
||||||
|
complex cd(0:NN*nss-1)
|
||||||
|
complex csymb(nss)
|
||||||
|
complex, allocatable, save :: c1(:,:) ! ideal waveforms, 4 tones
|
||||||
|
complex cp(0:3) ! accumulated phase shift over symbol types 0:3
|
||||||
|
complex csum,cterm
|
||||||
|
integer isyncword1(0:7),isyncword2(0:7)
|
||||||
|
integer graymap(0:3)
|
||||||
|
integer ip(1)
|
||||||
|
integer hmod
|
||||||
|
logical one(0:65535,0:15) ! 65536 8-symbol sequences, 16 bits
|
||||||
|
logical first
|
||||||
|
logical badsync
|
||||||
|
real bitmetrics(2*NN,4)
|
||||||
|
real s2(0:65535)
|
||||||
|
real s4(0:3,NN,4),s4hmod(0:3,NN)
|
||||||
|
data isyncword1/0,1,3,2,1,0,2,3/
|
||||||
|
data isyncword2/2,3,1,0,3,2,0,1/
|
||||||
|
data graymap/0,1,3,2/
|
||||||
|
data first/.true./,nss0/-1/
|
||||||
|
save first,one,cp,nss0
|
||||||
|
|
||||||
|
if(nss.ne.nss0 .and. allocated(c1)) deallocate(c1)
|
||||||
|
if(first .or. nss.ne.nss0) then
|
||||||
|
allocate(c1(nss,0:3))
|
||||||
|
one=.false.
|
||||||
|
do i=0,65535
|
||||||
|
do j=0,15
|
||||||
|
if(iand(i,2**j).ne.0) one(i,j)=.true.
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
twopi=8.0*atan(1.0)
|
||||||
|
dphi=twopi*hmod/nss
|
||||||
|
do itone=0,3
|
||||||
|
dp=(itone-1.5)*dphi
|
||||||
|
phi=0.0
|
||||||
|
do j=1,nss
|
||||||
|
c1(j,itone)=cmplx(cos(phi),sin(phi))
|
||||||
|
phi=mod(phi+dp,twopi)
|
||||||
|
enddo
|
||||||
|
cp(itone)=cmplx(cos(phi),sin(phi))
|
||||||
|
enddo
|
||||||
|
first=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
do k=1,NN
|
||||||
|
i1=(k-1)*NSS
|
||||||
|
csymb=cd(i1:i1+NSS-1)
|
||||||
|
do itone=0,3
|
||||||
|
s4(itone,k,1)=abs(sum(csymb*conjg(c1(:,itone))))
|
||||||
|
s4(itone,k,2)=abs(sum(csymb( 1:nss/2)*conjg(c1( 1:nss/2,itone)))) + &
|
||||||
|
abs(sum(csymb(nss/2+1: nss)*conjg(c1(nss/2+1: nss,itone))))
|
||||||
|
s4(itone,k,3)=abs(sum(csymb( 1: nss/4)*conjg(c1( 1: nss/4,itone)))) + &
|
||||||
|
abs(sum(csymb( nss/4+1: nss/2)*conjg(c1( nss/4+1: nss/2,itone)))) + &
|
||||||
|
abs(sum(csymb( nss/2+1:3*nss/4)*conjg(c1( nss/2+1:3*nss/4,itone)))) + &
|
||||||
|
abs(sum(csymb(3*nss/4+1: nss)*conjg(c1(3*nss/4+1: nss,itone))))
|
||||||
|
s4(itone,k,4)=abs(sum(csymb( 1: nss/8)*conjg(c1( 1: nss/8,itone)))) + &
|
||||||
|
abs(sum(csymb( nss/8+1: nss/4)*conjg(c1( nss/8+1: nss/4,itone)))) + &
|
||||||
|
abs(sum(csymb( nss/4+1:3*nss/8)*conjg(c1( nss/4+1:3*nss/8,itone)))) + &
|
||||||
|
abs(sum(csymb(3*nss/8+1: nss/2)*conjg(c1(3*nss/8+1: nss/2,itone)))) + &
|
||||||
|
abs(sum(csymb( nss/2+1:5*nss/8)*conjg(c1( nss/2+1:5*nss/8,itone)))) + &
|
||||||
|
abs(sum(csymb(5*nss/8+1:3*nss/4)*conjg(c1(5*nss/8+1:3*nss/4,itone)))) + &
|
||||||
|
abs(sum(csymb(3*nss/4+1:7*nss/8)*conjg(c1(3*nss/4+1:7*nss/8,itone)))) + &
|
||||||
|
abs(sum(csymb(7*nss/8+1: nss)*conjg(c1(7*nss/8+1: nss,itone))))
|
||||||
|
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
! Sync quality check
|
||||||
|
is1=0
|
||||||
|
is2=0
|
||||||
|
is3=0
|
||||||
|
is4=0
|
||||||
|
is5=0
|
||||||
|
badsync=.false.
|
||||||
|
ibmax=0
|
||||||
|
|
||||||
|
is1=0; is2=0; is3=0; is4=0; is5=0
|
||||||
|
do k=1,8
|
||||||
|
ip=maxloc(s4(:,k,1))
|
||||||
|
if(isyncword1(k-1).eq.(ip(1)-1)) is1=is1+1
|
||||||
|
ip=maxloc(s4(:,k+38,1))
|
||||||
|
if(isyncword2(k-1).eq.(ip(1)-1)) is2=is2+1
|
||||||
|
ip=maxloc(s4(:,k+76,1))
|
||||||
|
if(isyncword1(k-1).eq.(ip(1)-1)) is3=is3+1
|
||||||
|
ip=maxloc(s4(:,k+114,1))
|
||||||
|
if(isyncword2(k-1).eq.(ip(1)-1)) is4=is4+1
|
||||||
|
ip=maxloc(s4(:,k+152,1))
|
||||||
|
if(isyncword1(k-1).eq.(ip(1)-1)) is5=is5+1
|
||||||
|
enddo
|
||||||
|
nsync=is1+is2+is3+is4+is5 !Number of correct hard sync symbols, 0-40
|
||||||
|
badsync=.false.
|
||||||
|
|
||||||
|
if(nsync .lt. 16) then
|
||||||
|
badsync=.true.
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
|
||||||
|
bitmetrics=0.0
|
||||||
|
do nsub=1,nsizes
|
||||||
|
do ks=1,NN
|
||||||
|
s2=0
|
||||||
|
do i=0,3
|
||||||
|
s2(i)=s4(graymap(i),ks,nsub)
|
||||||
|
enddo
|
||||||
|
ipt=1+(ks-1)*2
|
||||||
|
ibmax=1
|
||||||
|
do ib=0,ibmax
|
||||||
|
bm=maxval(s2(0:3),one(0:3,ibmax-ib)) - &
|
||||||
|
maxval(s2(0:3),.not.one(0:3,ibmax-ib))
|
||||||
|
if(ipt+ib.gt.2*NN) cycle
|
||||||
|
bitmetrics(ipt+ib,nsub)=bm
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
call normalizebmet(bitmetrics(:,1),2*NN)
|
||||||
|
call normalizebmet(bitmetrics(:,2),2*NN)
|
||||||
|
call normalizebmet(bitmetrics(:,3),2*NN)
|
||||||
|
call normalizebmet(bitmetrics(:,4),2*NN)
|
||||||
|
|
||||||
|
! Return the s4 array corresponding to N=1/hmod. Will be used for SNR calculation
|
||||||
|
if(hmod.eq.1) s4hmod(:,:)=s4(:,:,1)
|
||||||
|
if(hmod.eq.2) s4hmod(:,:)=s4(:,:,2)
|
||||||
|
if(hmod.eq.4) s4hmod(:,:)=s4(:,:,3)
|
||||||
|
if(hmod.eq.8) s4hmod(:,:)=s4(:,:,4)
|
||||||
|
return
|
||||||
|
|
||||||
|
end subroutine get_fst240_bitmetrics2
|
@ -83,6 +83,8 @@ contains
|
|||||||
dxcall13=hiscall ! initialize for use in packjt77
|
dxcall13=hiscall ! initialize for use in packjt77
|
||||||
mycall13=mycall
|
mycall13=mycall
|
||||||
|
|
||||||
|
fMHz=10.0
|
||||||
|
|
||||||
if(first) then
|
if(first) then
|
||||||
mcq=2*mod(mcq+rvec(1:29),2)-1
|
mcq=2*mod(mcq+rvec(1:29),2)-1
|
||||||
mrrr=2*mod(mrrr+rvec(59:77),2)-1
|
mrrr=2*mod(mrrr+rvec(59:77),2)-1
|
||||||
@ -217,7 +219,7 @@ contains
|
|||||||
|
|
||||||
|
|
||||||
if(ndepth.eq.3) then
|
if(ndepth.eq.3) then
|
||||||
nblock=1
|
nblock=4
|
||||||
if(hmod.eq.1) nblock=4 ! number of block sizes to try
|
if(hmod.eq.1) nblock=4 ! number of block sizes to try
|
||||||
jittermax=2
|
jittermax=2
|
||||||
norder=3
|
norder=3
|
||||||
@ -252,6 +254,20 @@ contains
|
|||||||
itype2=2
|
itype2=2
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
if(hmod.eq.1) then
|
||||||
|
if(fMHz.lt.2.0) then
|
||||||
|
nsyncoh=8 ! Use N=8 for sync
|
||||||
|
nhicoh=1 ! Use N=1,2,4,8 for symbol estimation
|
||||||
|
else
|
||||||
|
nsyncoh=4 ! Use N=4 for sync
|
||||||
|
nhicoh=0 ! Use N=1,2,3,4 for symbol estimation
|
||||||
|
endif
|
||||||
|
else
|
||||||
|
if(hmod.eq.2) nsyncoh=1
|
||||||
|
if(hmod.eq.4) nsyncoh=1
|
||||||
|
if(hmod.eq.8) nsyncoh=1
|
||||||
|
endif
|
||||||
|
|
||||||
do iqorw=itype1,itype2 ! iqorw=1 for QSO mode and iqorw=2 for wspr-type messages
|
do iqorw=itype1,itype2 ! iqorw=1 for QSO mode and iqorw=2 for wspr-type messages
|
||||||
if( iwspr.lt.2 ) then
|
if( iwspr.lt.2 ) then
|
||||||
if( single_decode ) then
|
if( single_decode ) then
|
||||||
@ -278,10 +294,8 @@ contains
|
|||||||
ndecodes=0
|
ndecodes=0
|
||||||
decodes=' '
|
decodes=' '
|
||||||
|
|
||||||
isbest1=0
|
isbest=0
|
||||||
isbest8=0
|
fc2=0.
|
||||||
fc21=0.
|
|
||||||
fc28=0.
|
|
||||||
do icand=1,ncand
|
do icand=1,ncand
|
||||||
fc0=candidates(icand,1)
|
fc0=candidates(icand,1)
|
||||||
detmet=candidates(icand,2)
|
detmet=candidates(icand,2)
|
||||||
@ -308,47 +322,29 @@ contains
|
|||||||
ifhw=12
|
ifhw=12
|
||||||
df=.1*baud
|
df=.1*baud
|
||||||
else if(isync.eq.1) then
|
else if(isync.eq.1) then
|
||||||
fc1=fc21
|
fc1=fc2
|
||||||
if(hmod.eq.1) fc1=fc28
|
is0=isbest
|
||||||
is0=isbest1
|
|
||||||
if(hmod.eq.1) is0=isbest8
|
|
||||||
ishw=4*hmod
|
ishw=4*hmod
|
||||||
isst=1*hmod
|
isst=1*hmod
|
||||||
ifhw=7
|
ifhw=7
|
||||||
df=.02*baud
|
df=.02*baud
|
||||||
endif
|
endif
|
||||||
|
|
||||||
smax1=0.0
|
smax=0.0
|
||||||
smax8=0.0
|
|
||||||
do if=-ifhw,ifhw
|
do if=-ifhw,ifhw
|
||||||
fc=fc1+df*if
|
fc=fc1+df*if
|
||||||
do istart=max(1,is0-ishw),is0+ishw,isst
|
do istart=max(1,is0-ishw),is0+ishw,isst
|
||||||
call sync_fst240(c2,istart,fc,hmod,1,nfft2,nss,fs2,sync1)
|
call sync_fst240(c2,istart,fc,hmod,nsyncoh,nfft2,nss,fs2,sync)
|
||||||
call sync_fst240(c2,istart,fc,hmod,8,nfft2,nss,fs2,sync8)
|
if(sync.gt.smax) then
|
||||||
if(sync8.gt.smax8) then
|
fc2=fc
|
||||||
fc28=fc
|
isbest=istart
|
||||||
isbest8=istart
|
smax=sync
|
||||||
smax8=sync8
|
|
||||||
endif
|
|
||||||
if(sync1.gt.smax1) then
|
|
||||||
fc21=fc
|
|
||||||
isbest1=istart
|
|
||||||
smax1=sync1
|
|
||||||
endif
|
endif
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
call timer('sync240 ',1)
|
call timer('sync240 ',1)
|
||||||
|
|
||||||
if(smax8/smax1 .lt. 0.65 ) then
|
|
||||||
fc2=fc21
|
|
||||||
isbest=isbest1
|
|
||||||
njitter=2
|
|
||||||
else
|
|
||||||
fc2=fc28
|
|
||||||
isbest=isbest8
|
|
||||||
njitter=2
|
|
||||||
endif
|
|
||||||
fc_synced = fc0 + fc2
|
fc_synced = fc0 + fc2
|
||||||
dt_synced = (isbest-fs2)*dt2 !nominal dt is 1 second so frame starts at sample fs2
|
dt_synced = (isbest-fs2)*dt2 !nominal dt is 1 second so frame starts at sample fs2
|
||||||
candidates(icand,3)=fc_synced
|
candidates(icand,3)=fc_synced
|
||||||
@ -387,6 +383,7 @@ contains
|
|||||||
fc_synced=candidates(icand,3)
|
fc_synced=candidates(icand,3)
|
||||||
isbest=nint(candidates(icand,4))
|
isbest=nint(candidates(icand,4))
|
||||||
xdt=(isbest-nspsec)/fs2
|
xdt=(isbest-nspsec)/fs2
|
||||||
|
|
||||||
if(ntrperiod.eq.15) xdt=(isbest-real(nspsec)/2.0)/fs2
|
if(ntrperiod.eq.15) xdt=(isbest-real(nspsec)/2.0)/fs2
|
||||||
call fst240_downsample(c_bigfft,nfft1,ndown,fc_synced,sigbw,c2)
|
call fst240_downsample(c_bigfft,nfft1,ndown,fc_synced,sigbw,c2)
|
||||||
|
|
||||||
@ -398,7 +395,11 @@ contains
|
|||||||
if(is0.lt.0) cycle
|
if(is0.lt.0) cycle
|
||||||
cframe=c2(is0:is0+160*nss-1)
|
cframe=c2(is0:is0+160*nss-1)
|
||||||
bitmetrics=0
|
bitmetrics=0
|
||||||
call get_fst240_bitmetrics(cframe,nss,hmod,nblock,bitmetrics,s4,badsync)
|
if(hmod.eq.1) then
|
||||||
|
call get_fst240_bitmetrics(cframe,nss,hmod,nblock,nhicoh,bitmetrics,s4,badsync)
|
||||||
|
else
|
||||||
|
call get_fst240_bitmetrics2(cframe,nss,hmod,nblock,bitmetrics,s4,badsync)
|
||||||
|
endif
|
||||||
if(badsync) cycle
|
if(badsync) cycle
|
||||||
|
|
||||||
hbits=0
|
hbits=0
|
||||||
@ -409,7 +410,7 @@ contains
|
|||||||
ns4=count(hbits(229:244).eq.(/1,1,1,0,0,1,0,0,1,0,1,1,0,0,0,1/))
|
ns4=count(hbits(229:244).eq.(/1,1,1,0,0,1,0,0,1,0,1,1,0,0,0,1/))
|
||||||
ns5=count(hbits(305:320).eq.(/0,0,0,1,1,0,1,1,0,1,0,0,1,1,1,0/))
|
ns5=count(hbits(305:320).eq.(/0,0,0,1,1,0,1,1,0,1,0,0,1,1,1,0/))
|
||||||
nsync_qual=ns1+ns2+ns3+ns4+ns5
|
nsync_qual=ns1+ns2+ns3+ns4+ns5
|
||||||
if(nsync_qual.lt. 46) cycle !### Value ?? ###
|
! if(nsync_qual.lt. 46) cycle !### Value ?? ###
|
||||||
|
|
||||||
scalefac=2.83
|
scalefac=2.83
|
||||||
llra( 1: 60)=bitmetrics( 17: 76, 1)
|
llra( 1: 60)=bitmetrics( 17: 76, 1)
|
||||||
@ -529,7 +530,7 @@ contains
|
|||||||
do i=1,ndecodes
|
do i=1,ndecodes
|
||||||
if(decodes(i).eq.msg) idupe=1
|
if(decodes(i).eq.msg) idupe=1
|
||||||
enddo
|
enddo
|
||||||
if(idupe.eq.1) exit
|
if(idupe.eq.1) goto 2002
|
||||||
ndecodes=ndecodes+1
|
ndecodes=ndecodes+1
|
||||||
decodes(ndecodes)=msg
|
decodes(ndecodes)=msg
|
||||||
|
|
||||||
@ -554,9 +555,9 @@ contains
|
|||||||
nsnr=nint(xsnr)
|
nsnr=nint(xsnr)
|
||||||
qual=0.
|
qual=0.
|
||||||
fsig=fc_synced - 1.5*hmod*baud
|
fsig=fc_synced - 1.5*hmod*baud
|
||||||
!write(21,'(i6,7i6,f7.1,f9.2,f7.1,1x,f7.2,1x,f7.1,1x,a37)') &
|
write(21,'(i6,8i6,f7.1,f9.2,f7.1,1x,f7.2,1x,f7.1,1x,a37)') &
|
||||||
! nutc,icand,itry,iaptype,ijitter,ntype,nsync_qual,nharderrors,dmin,sync,xsnr,xdt,fsig,msg
|
nutc,icand,itry,nsyncoh,iaptype,ijitter,ntype,nsync_qual,nharderrors,dmin,sync,xsnr,xdt,fsig,msg
|
||||||
!flush(21)
|
flush(21)
|
||||||
call this%callback(nutc,smax1,nsnr,xdt,fsig,msg, &
|
call this%callback(nutc,smax1,nsnr,xdt,fsig,msg, &
|
||||||
iaptype,qual,ntrperiod,lwspr)
|
iaptype,qual,ntrperiod,lwspr)
|
||||||
goto 2002
|
goto 2002
|
||||||
@ -637,28 +638,47 @@ contains
|
|||||||
s4=0.0
|
s4=0.0
|
||||||
s5=0.0
|
s5=0.0
|
||||||
|
|
||||||
nsec=8/ncoh
|
if(ncoh.gt.0) then
|
||||||
do i=1,nsec
|
nsec=8/ncoh
|
||||||
is=(i-1)*ncoh*nss
|
do i=1,nsec
|
||||||
z1=0
|
is=(i-1)*ncoh*nss
|
||||||
if(i1+is.ge.1) then
|
z1=0
|
||||||
z1=sum(cd0(i1+is:i1+is+ncoh*nss-1)*conjg(csynct1(is+1:is+ncoh*nss)))
|
if(i1+is.ge.1) then
|
||||||
endif
|
z1=sum(cd0(i1+is:i1+is+ncoh*nss-1)*conjg(csynct1(is+1:is+ncoh*nss)))
|
||||||
z2=sum(cd0(i2+is:i2+is+ncoh*nss-1)*conjg(csynct2(is+1:is+ncoh*nss)))
|
endif
|
||||||
z3=sum(cd0(i3+is:i3+is+ncoh*nss-1)*conjg(csynct1(is+1:is+ncoh*nss)))
|
z2=sum(cd0(i2+is:i2+is+ncoh*nss-1)*conjg(csynct2(is+1:is+ncoh*nss)))
|
||||||
z4=sum(cd0(i4+is:i4+is+ncoh*nss-1)*conjg(csynct2(is+1:is+ncoh*nss)))
|
z3=sum(cd0(i3+is:i3+is+ncoh*nss-1)*conjg(csynct1(is+1:is+ncoh*nss)))
|
||||||
z5=0
|
z4=sum(cd0(i4+is:i4+is+ncoh*nss-1)*conjg(csynct2(is+1:is+ncoh*nss)))
|
||||||
if(i5+is+ncoh*nss-1.le.np) then
|
z5=0
|
||||||
z5=sum(cd0(i5+is:i5+is+ncoh*nss-1)*conjg(csynct1(is+1:is+ncoh*nss)))
|
if(i5+is+ncoh*nss-1.le.np) then
|
||||||
endif
|
z5=sum(cd0(i5+is:i5+is+ncoh*nss-1)*conjg(csynct1(is+1:is+ncoh*nss)))
|
||||||
s1=s1+abs(z1)/(8*nss)
|
endif
|
||||||
s2=s2+abs(z2)/(8*nss)
|
s1=s1+abs(z1)/(8*nss)
|
||||||
s3=s3+abs(z3)/(8*nss)
|
s2=s2+abs(z2)/(8*nss)
|
||||||
s4=s4+abs(z4)/(8*nss)
|
s3=s3+abs(z3)/(8*nss)
|
||||||
s5=s5+abs(z5)/(8*nss)
|
s4=s4+abs(z4)/(8*nss)
|
||||||
enddo
|
s5=s5+abs(z5)/(8*nss)
|
||||||
|
enddo
|
||||||
|
else
|
||||||
|
nsub=-ncoh
|
||||||
|
nps=nss/nsub
|
||||||
|
do i=1,8
|
||||||
|
do isub=1,nsub
|
||||||
|
is=(i-1)*nss+(isub-1)*nps
|
||||||
|
if(i1+is.ge.1) then
|
||||||
|
s1=s1+abs(sum(cd0(i1+is:i1+is+nps-1)*conjg(csynct1(is+1:is+nps))))
|
||||||
|
endif
|
||||||
|
s2=s2+abs(sum(cd0(i2+is:i2+is+nps-1)*conjg(csynct1(is+1:is+nps))))
|
||||||
|
s3=s3+abs(sum(cd0(i3+is:i3+is+nps-1)*conjg(csynct1(is+1:is+nps))))
|
||||||
|
s4=s4+abs(sum(cd0(i4+is:i4+is+nps-1)*conjg(csynct1(is+1:is+nps))))
|
||||||
|
s5=0
|
||||||
|
if(i5+is+ncoh*nss-1.le.np) then
|
||||||
|
s5=s5+abs(sum(cd0(i5+is:i5+is+nps-1)*conjg(csynct1(is+1:is+nps))))
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
endif
|
||||||
sync = s1+s2+s3+s4+s5
|
sync = s1+s2+s3+s4+s5
|
||||||
|
|
||||||
return
|
return
|
||||||
end subroutine sync_fst240
|
end subroutine sync_fst240
|
||||||
|
|
||||||
|
Loading…
Reference in New Issue
Block a user