2012-11-06 21:28:59 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								subroutine spec9(c0,npts8,nsps,fpk0,fpk,xdt,snrdb,i1SoftSymbols)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  parameter (MAXFFT=31500)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  complex c0(0:npts8-1)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-19 19:26:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  complex c1(0:2700000)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-12 18:28:28 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  real*4 ssym(0:7,69)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  real*4 sx(0:31500-1)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  complex c(0:MAXFFT-1)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 12:39:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer*1 i1SoftSymbolsScrambled(207)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer*1 i1SoftSymbols(207)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer*1 i1
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 12:39:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer ig(0:7)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  equivalence (i1,i4)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:31:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  data ig/0,1,3,2,7,6,4,5/             !Gray code removal
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-22 19:18:24 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  include 'jt9sync.f90'
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-10 20:40:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								! Fix up the data in c0()
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 20:52:29 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  sum=0.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  do i=0,npts8-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     sum=sum + real(c0(i))**2 + aimag(c0(i))**2
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  rms=sqrt(sum/npts8)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  fac=1.0/rms
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-10 20:40:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  twopi=8.0*atan(1.0)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  phi=0.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  dphi=twopi*500.0/1500.0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  do i=0,npts8-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     phi=phi+dphi
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     if(phi.gt.twopi) phi=phi-twopi
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     if(phi.lt.-twopi) phi=phi+twopi
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 20:52:29 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     c1(i)=fac*cmplx(aimag(c0(i)),real(c0(i)))*cmplx(cos(phi),sin(phi))
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-10 20:40:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:31:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  nsps8=nsps/8
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 20:52:29 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  foffset=fpk0
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 17:47:55 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  istart=1520
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-14 15:30:21 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call timer('peakdt9 ',0)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-19 19:26:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call peakdt9(c1,npts8,nsps8,istart,foffset,idt)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-14 15:30:21 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call timer('peakdt9 ',1)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 18:39:37 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  istart=istart + 0.0625*nsps8*idt
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  xdt=istart/1500.0 - 1.0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-14 15:30:21 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call timer('peakdf9 ',0)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-13 20:23:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call peakdf9(c1,npts8,nsps8,istart,foffset,idf)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-14 15:30:21 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call timer('peakdf9 ',1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-13 20:23:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  fpk=fpk0 + idf*0.1*1500.0/nsps8
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  foffset=foffset + idf*0.1*1500.0/nsps8
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-14 15:30:21 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  twopi=8.0*atan(1.0)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-13 20:23:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  dphi=twopi*foffset/1500.0
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  nfft=nsps8
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  nsym=min((npts8-istart)/nsps8,85)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:42:48 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  k=0
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:31:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  do j=1,nsym
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:42:48 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     if(isync(j).eq.1) cycle
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     k=k+1
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:31:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     ia=(j-1)*nsps8 + istart
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-13 20:23:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								!     c(0:nfft-1)=c1(ia:ib)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do i=0,nfft-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        c(i)=0.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(ia+i.ge.0 .and. ia+i.lt.2700000-1) c(i)=c1(ia+i)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     enddo
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     phi=0.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do i=0,nfft-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        phi=phi + dphi
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        c(i)=c(i) * cmplx(cos(phi),-sin(phi))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     call four2a(c,nfft,1,-1,1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do i=0,nfft-1
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-12 18:28:28 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        sx(i)=real(c(i))**2 + aimag(c(i))**2
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(i.ge.1 .and. i.le.8) ssym(ig(i-1),k)=sx(i)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  sum=0.
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 21:28:59 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  sig=0.
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  do j=1,69
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     smax=0.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do i=0,7
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        smax=max(smax,ssym(i,j))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        sum=sum+ssym(i,j)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     enddo
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 21:28:59 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     sig=sig+smax
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     sum=sum-smax
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ave=sum/(69*7)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-12 18:28:28 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call pctile(sx,nsps8,50,xmed)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  ssym=ssym/ave
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 21:28:59 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  sig=sig/69.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  df8=1500.0/nsps8
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-12 18:28:28 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  t=max(1.0,sig/xmed - 1.0)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  snrdb=db(t) - db(2500.0/df8) - 5.0
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  m0=3
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ntones=8
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  k=0
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:42:48 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  do j=1,69
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do m=m0-1,0,-1                   !Get bit-wise soft symbols
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        n=2**m
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        r1=0.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        r2=0.
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 12:39:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        do i=0,ntones-1
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           if(iand(i,n).ne.0) then
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:42:48 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								              r1=max(r1,ssym(i,j))
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           else
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 16:42:48 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								              r2=max(r2,ssym(i,j))
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        k=k+1
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        i4=nint(10.0*(r1-r2))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(i4.lt.-127) i4=-127
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(i4.gt.127) i4=127
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        i4=i4+128
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        i1SoftSymbolsScrambled(k)=i1
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-03 12:39:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call interleave9(i1SoftSymbolsScrambled,-1,i1SoftSymbols)
							 | 
						
					
						
							
								
									
										
										
										
											2012-11-06 19:49:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  call flush(81)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  call flush(82)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-02 18:08:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  return
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								end subroutine spec9
							 |