| 
									
										
										
										
											2020-06-17 19:28:44 -04:00
										 |  |  | subroutine symspec(shared_data,k,TRperiod,nsps,ingain,bLowSidelobes,    &
 | 
					
						
							| 
									
										
										
										
											2020-07-23 10:58:10 -04:00
										 |  |  |      nminw,pxdb,s,df3,ihsym,npts8,pxdbmax,npct)
 | 
					
						
							| 
									
										
										
										
											2012-05-22 17:09:48 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2012-10-01 19:05:22 +00:00
										 |  |  | ! Input:
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:04:05 -05:00
										 |  |  | !  k              pointer to the most recent new data
 | 
					
						
							| 
									
										
										
										
											2020-06-17 19:28:44 -04:00
										 |  |  | !  TRperiod       T/R sequence length, seconds
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:04:05 -05:00
										 |  |  | !  nsps           samples per symbol, at 12000 Hz
 | 
					
						
							|  |  |  | !  bLowSidelobes  true to use windowed FFTs
 | 
					
						
							|  |  |  | !  ndiskdat       0/1 to indicate if data from disk
 | 
					
						
							| 
									
										
										
										
											2012-10-01 19:05:22 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | ! Output:
 | 
					
						
							| 
									
										
										
										
											2017-03-06 15:52:09 +00:00
										 |  |  | !  pxdb      raw power (0-90 dB)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | !  s()       current spectrum for waterfall display
 | 
					
						
							| 
									
										
										
										
											2015-05-27 13:08:28 +00:00
										 |  |  | !  ihsym     index number of this half-symbol (1-184) for 60 s modes
 | 
					
						
							| 
									
										
										
										
											2012-05-22 17:09:48 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | ! jt9com
 | 
					
						
							|  |  |  | !  ss()      JT9 symbol spectra at half-symbol steps
 | 
					
						
							|  |  |  | !  savg()    average spectra for waterfall display
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-27 15:40:57 +00:00
										 |  |  |   use, intrinsic :: iso_c_binding, only: c_int, c_short, c_float, c_char
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   include 'jt9com.f90'
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   type(dec_data) :: shared_data
 | 
					
						
							| 
									
										
										
										
											2020-06-17 19:28:44 -04:00
										 |  |  |   real*8 TRperiod
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   real*4 w3(MAXFFT3)
 | 
					
						
							|  |  |  |   real*4 s(NSMAX)
 | 
					
						
							| 
									
										
										
										
											2012-10-11 18:33:50 +00:00
										 |  |  |   real*4 ssum(NSMAX)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   real*4 xc(0:MAXFFT3-1)
 | 
					
						
							| 
									
										
										
										
											2014-03-05 18:20:40 +00:00
										 |  |  |   real*4 tmp(NSMAX)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   complex cx(0:MAXFFT3/2)
 | 
					
						
							| 
									
										
										
										
											2015-05-27 13:08:28 +00:00
										 |  |  |   integer nch(7)
 | 
					
						
							| 
									
										
										
										
											2020-07-23 10:58:10 -04:00
										 |  |  |   logical*1 bLowSidelobes
 | 
					
						
							| 
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |   common/spectra/syellow(NSMAX),ref(0:3456),filter(0:3456)
 | 
					
						
							| 
									
										
										
										
											2017-03-06 15:52:09 +00:00
										 |  |  |   data k0/99999999/,nfft3z/0/
 | 
					
						
							| 
									
										
										
										
											2015-05-27 13:08:28 +00:00
										 |  |  |   data nch/1,2,4,9,18,36,72/
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   equivalence (xc,cx)
 | 
					
						
							| 
									
										
										
										
											2012-05-22 17:09:48 +00:00
										 |  |  |   save
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2021-01-06 12:44:49 -05:00
										 |  |  |   if(TRperiod+npct.eq.-999.9) stop             !Silence compiler warning
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   nfft3=16384                                  !df=12000.0/16384 = 0.732422
 | 
					
						
							|  |  |  |   jstep=nsps/2                                 !Step size = half-symbol in id2()
 | 
					
						
							|  |  |  |   if(k.gt.NMAX) go to 900
 | 
					
						
							|  |  |  |   if(k.lt.2048) then                !(2048 was nfft3)  (Any need for this ???)
 | 
					
						
							| 
									
										
										
										
											2012-05-22 17:09:48 +00:00
										 |  |  |      ihsym=0
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |      go to 900                                 !Wait for enough samples to start
 | 
					
						
							| 
									
										
										
										
											2012-05-22 17:09:48 +00:00
										 |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-01-17 14:46:23 +00:00
										 |  |  |   if(nfft3.ne.nfft3z) then
 | 
					
						
							|  |  |  | ! Compute new window
 | 
					
						
							| 
									
										
										
										
											2012-05-22 17:09:48 +00:00
										 |  |  |      pi=4.0*atan(1.0)
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |      w3=0
 | 
					
						
							|  |  |  |      call nuttal_window(w3,nfft3)
 | 
					
						
							| 
									
										
										
										
											2012-10-01 19:05:22 +00:00
										 |  |  |      nfft3z=nfft3
 | 
					
						
							| 
									
										
										
										
											2012-05-22 17:09:48 +00:00
										 |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2012-10-01 00:02:36 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-04-22 15:43:02 +00:00
										 |  |  |   if(k.lt.k0) then                             !Start a new data block
 | 
					
						
							| 
									
										
										
										
											2012-11-12 21:06:31 +00:00
										 |  |  |      ja=0
 | 
					
						
							| 
									
										
										
										
											2012-10-11 18:33:50 +00:00
										 |  |  |      ssum=0.
 | 
					
						
							| 
									
										
										
										
											2012-06-04 17:02:50 +00:00
										 |  |  |      ihsym=0
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |      if(.not. shared_data%params%ndiskdat) shared_data%id2(k+1:)=0   !Needed to prevent "ghosts". Not sure why.
 | 
					
						
							| 
									
										
										
										
											2012-06-04 17:02:50 +00:00
										 |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2014-01-17 14:56:11 +00:00
										 |  |  |   gain=10.0**(0.1*ingain)
 | 
					
						
							| 
									
										
										
										
											2013-05-16 23:52:04 +00:00
										 |  |  |   sq=0.
 | 
					
						
							| 
									
										
										
										
											2017-03-06 14:34:25 +00:00
										 |  |  |   pxmax=0.;
 | 
					
						
							| 
									
										
										
										
											2020-07-14 11:27:41 -04:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2020-07-23 10:58:10 -04:00
										 |  |  | !  dwell_time=0.0001
 | 
					
						
							|  |  |  | !  if(k.gt.k0 .and. npct.gt.0) call blanker(shared_data%id2(k0+1:k),  &
 | 
					
						
							|  |  |  | !       k-k0,dwell_time,npct)
 | 
					
						
							| 
									
										
										
										
											2020-07-14 11:27:41 -04:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   do i=k0+1,k
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |      x1=shared_data%id2(i)
 | 
					
						
							| 
									
										
										
										
											2017-03-06 14:34:25 +00:00
										 |  |  |      if (abs(x1).gt.pxmax) pxmax = abs(x1);
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |      sq=sq + x1*x1
 | 
					
						
							| 
									
										
										
										
											2012-10-01 19:05:22 +00:00
										 |  |  |   enddo
 | 
					
						
							| 
									
										
										
										
											2017-03-06 15:52:09 +00:00
										 |  |  |   pxdb = 0.
 | 
					
						
							|  |  |  |   if(sq.gt.0.0) pxdb=10*log10(sq/(k-k0))
 | 
					
						
							|  |  |  |   pxdbmax=0.
 | 
					
						
							|  |  |  |   if(pxmax.gt.0) pxdbmax = 20*log10(pxmax)
 | 
					
						
							| 
									
										
										
										
											2012-10-04 02:05:14 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   k0=k
 | 
					
						
							|  |  |  |   ja=ja+jstep                         !Index of first sample
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   fac0=0.1
 | 
					
						
							| 
									
										
										
										
											2012-11-12 21:09:32 +00:00
										 |  |  |   do i=0,nfft3-1                      !Copy data into cx
 | 
					
						
							|  |  |  |      j=ja+i-(nfft3-1)
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |      xc(i)=0.
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |      if(j.ge.1 .and.j.le.NMAX) xc(i)=fac0*shared_data%id2(j)
 | 
					
						
							| 
									
										
										
										
											2012-11-12 21:09:32 +00:00
										 |  |  |   enddo
 | 
					
						
							| 
									
										
										
										
											2015-05-27 13:08:28 +00:00
										 |  |  |   ihsym=ihsym+1
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:04:05 -05:00
										 |  |  |   if(bLowSidelobes) xc(0:nfft3-1)=w3(1:nfft3)*xc(0:nfft3-1)    !Apply window 
 | 
					
						
							|  |  |  |   call four2a(xc,nfft3,1,-1,0)        !Real-to-complex FFT
 | 
					
						
							| 
									
										
										
										
											2012-11-12 21:09:32 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:04:05 -05:00
										 |  |  |   df3=12000.0/nfft3                   !JT9: 0.732 Hz = 0.42 * tone spacing
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  |   iz=min(NSMAX,nint(5000.0/df3))
 | 
					
						
							| 
									
										
										
										
											2012-11-12 21:09:32 +00:00
										 |  |  |   fac=(1.0/nfft3)**2
 | 
					
						
							|  |  |  |   do i=1,iz
 | 
					
						
							| 
									
										
										
										
											2015-05-27 13:08:28 +00:00
										 |  |  |      j=i-1
 | 
					
						
							| 
									
										
										
										
											2012-11-12 21:09:32 +00:00
										 |  |  |      if(j.lt.0) j=j+nfft3
 | 
					
						
							|  |  |  |      sx=fac*(real(cx(j))**2 + aimag(cx(j))**2)
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |      if(ihsym.le.184) shared_data%ss(ihsym,i)=sx
 | 
					
						
							| 
									
										
										
										
											2012-11-12 21:09:32 +00:00
										 |  |  |      ssum(i)=ssum(i) + sx
 | 
					
						
							| 
									
										
										
										
											2014-01-17 14:56:11 +00:00
										 |  |  |      s(i)=1000.0*gain*sx
 | 
					
						
							| 
									
										
										
										
											2012-11-12 21:09:32 +00:00
										 |  |  |   enddo
 | 
					
						
							| 
									
										
										
										
											2012-05-22 17:09:48 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   shared_data%savg=ssum/ihsym
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-05-27 13:08:28 +00:00
										 |  |  |   if(mod(ihsym,10).eq.0) then
 | 
					
						
							|  |  |  |      mode4=nch(nminw+1)
 | 
					
						
							| 
									
										
										
										
											2014-03-05 18:20:40 +00:00
										 |  |  |      nsmo=min(10*mode4,150)
 | 
					
						
							|  |  |  |      nsmo=4*nsmo
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |      call flat1(shared_data%savg,iz,nsmo,syellow)
 | 
					
						
							| 
									
										
										
										
											2015-05-27 13:08:28 +00:00
										 |  |  |      if(mode4.ge.2) call smo(syellow,iz,tmp,mode4)
 | 
					
						
							|  |  |  |      if(mode4.ge.2) call smo(syellow,iz,tmp,mode4)
 | 
					
						
							|  |  |  |      syellow(1:250)=0.
 | 
					
						
							| 
									
										
										
										
											2014-03-05 18:20:40 +00:00
										 |  |  |      ia=500./df3
 | 
					
						
							|  |  |  |      ib=2700.0/df3
 | 
					
						
							|  |  |  |      smin=minval(syellow(ia:ib))
 | 
					
						
							|  |  |  |      smax=maxval(syellow(1:iz))
 | 
					
						
							|  |  |  |      syellow=(50.0/(smax-smin))*(syellow-smin)
 | 
					
						
							|  |  |  |      where(syellow<0) syellow=0.
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2013-07-08 13:17:22 +00:00
										 |  |  | 900 npts8=k/8
 | 
					
						
							| 
									
										
										
										
											2012-10-15 17:43:49 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2012-10-04 19:03:39 +00:00
										 |  |  |   return
 | 
					
						
							| 
									
										
										
										
											2012-10-03 15:22:49 +00:00
										 |  |  | end subroutine symspec
 | 
					
						
							| 
									
										
										
										
											2020-08-09 14:21:25 -04:00
										 |  |  | 
 | 
					
						
							|  |  |  | subroutine chk_samples(ihsym,k,nstop)
 | 
					
						
							|  |  |  |   
 | 
					
						
							|  |  |  |   integer*8 count0,count1,clkfreq
 | 
					
						
							|  |  |  |   integer itime(8)
 | 
					
						
							|  |  |  |   real*8 dtime,fsample
 | 
					
						
							|  |  |  |   character*12 ctime
 | 
					
						
							|  |  |  |   data count0/-1/,k0/99999999/,maxhsym/0/
 | 
					
						
							|  |  |  |   save count0,k0,maxhsym
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   if(k.lt.k0 .or. count0.eq.-1) then
 | 
					
						
							|  |  |  |      call system_clock(count0,clkfreq)
 | 
					
						
							|  |  |  |      maxhsym=0
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2021-02-03 15:20:37 -05:00
										 |  |  | !  if((mod(ihsym,100).eq.0 .or. ihsym.ge.nstop-100) .and.       &
 | 
					
						
							|  |  |  | !       k0.ne.99999999) then
 | 
					
						
							|  |  |  | !     call system_clock(count1,clkfreq)
 | 
					
						
							|  |  |  | !     dtime=dfloat(count1-count0)/dfloat(clkfreq)
 | 
					
						
							|  |  |  | !     if(dtime.lt.28.0) return
 | 
					
						
							|  |  |  | !     if(dtime.gt.1.d-6) fsample=(k-3456)/dtime
 | 
					
						
							|  |  |  | !     call date_and_time(values=itime)
 | 
					
						
							|  |  |  | !     sec=itime(7)+0.001*itime(8)
 | 
					
						
							|  |  |  | !     write(ctime,3000) itime(5)-itime(4)/60,itime(6),sec
 | 
					
						
							|  |  |  | !3000 format(i2.2,':',i2.2,':',f6.3)
 | 
					
						
							|  |  |  | !     write(33,3033) ctime,dtime,ihsym,nstop,k,fsample
 | 
					
						
							|  |  |  | !3033 format(a12,f12.6,2i7,i10,f15.3)
 | 
					
						
							|  |  |  | !     flush(33)
 | 
					
						
							|  |  |  | !  endif
 | 
					
						
							| 
									
										
										
										
											2020-08-09 14:21:25 -04:00
										 |  |  |   k0=k
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   return
 | 
					
						
							|  |  |  | end subroutine chk_samples
 |