| 
									
										
										
										
											2017-07-16 00:10:37 +00:00
										 |  |  | subroutine refspectrum(id2,bclear,brefspec,buseref,fname)
 | 
					
						
							| 
									
										
										
										
											2016-04-08 15:55:28 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | ! Input:
 | 
					
						
							|  |  |  | !  id2       i*2        Raw 16-bit integer data, 12000 Hz sample rate
 | 
					
						
							|  |  |  | !  brefspec  logical    True when accumulating a reference spectrum
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |   parameter (NFFT=6912,NH=NFFT/2,NPOLYLOW=400,NPOLYHIGH=2600)
 | 
					
						
							| 
									
										
										
										
											2017-07-16 00:10:37 +00:00
										 |  |  |   integer*2 id2(NFFT)
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |   logical*1 bclear,brefspec,buseref,blastuse
 | 
					
						
							| 
									
										
										
										
											2017-02-22 20:43:40 +00:00
										 |  |  |   
 | 
					
						
							| 
									
										
										
										
											2017-07-15 15:46:46 +00:00
										 |  |  |   real xs(0:NH-1)                         !Saved upper half of input chunk convolved with h(t) 
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |   real x(0:NFFT-1)                        !Work array
 | 
					
						
							|  |  |  |   real*4 w(0:NFFT-1)                      !Window function
 | 
					
						
							|  |  |  |   real*4 s(0:NH)                          !Average spectrum
 | 
					
						
							|  |  |  |   real*4 fil(0:NH)
 | 
					
						
							| 
									
										
										
										
											2017-02-22 20:43:40 +00:00
										 |  |  |   real*8 xfit(1500),yfit(1500),sigmay(1500),a(5),chisqr !Polyfit arrays
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |   logical first
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |   complex cx(0:NH)                        !Complex frequency-domain work array
 | 
					
						
							| 
									
										
										
										
											2017-07-16 00:10:37 +00:00
										 |  |  |   complex cfil(0:NH)
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |   character*(*) fname
 | 
					
						
							|  |  |  |   common/spectra/syellow(6827),ref(0:NH),filter(0:NH)
 | 
					
						
							| 
									
										
										
										
											2016-04-08 18:07:08 +00:00
										 |  |  |   equivalence(x,cx)
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |   data first/.true./,blastuse/.false./
 | 
					
						
							| 
									
										
										
										
											2016-04-09 14:51:20 +00:00
										 |  |  |   save
 | 
					
						
							| 
									
										
										
										
											2016-04-08 15:55:28 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |   if(first) then
 | 
					
						
							|  |  |  |      pi=4.0*atan(1.0)
 | 
					
						
							|  |  |  |      do i=0,NFFT-1
 | 
					
						
							|  |  |  |         ww=sin(i*pi/NFFT)
 | 
					
						
							|  |  |  |         w(i)=ww*ww/NFFT
 | 
					
						
							|  |  |  |      enddo
 | 
					
						
							|  |  |  |      nsave=0
 | 
					
						
							|  |  |  |      s=0.0
 | 
					
						
							|  |  |  |      filter=1.0
 | 
					
						
							| 
									
										
										
										
											2017-07-15 15:43:41 +00:00
										 |  |  |      xs=0.
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |      first=.false.
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2016-12-24 20:05:28 +00:00
										 |  |  |   if(bclear) s=0.
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-08 18:07:08 +00:00
										 |  |  |   if(brefspec) then
 | 
					
						
							| 
									
										
										
										
											2016-04-18 14:37:44 +00:00
										 |  |  |      x(0:NH-1)=0.001*id2(1:NH)
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |      x(NH:NFFT-1)=0.0
 | 
					
						
							| 
									
										
										
										
											2020-02-21 13:36:49 -05:00
										 |  |  |      call four2a(cx,NFFT,1,-1,0)                 !r2c FFT
 | 
					
						
							| 
									
										
										
										
											2016-04-08 18:07:08 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |      do i=1,NH
 | 
					
						
							|  |  |  |         s(i)=s(i) + real(cx(i))**2 + aimag(cx(i))**2
 | 
					
						
							|  |  |  |      enddo
 | 
					
						
							|  |  |  |      nsave=nsave+1
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |      fac0=0.9
 | 
					
						
							|  |  |  |      if(mod(nsave,4).eq.0) then
 | 
					
						
							| 
									
										
										
										
											2016-04-08 18:07:08 +00:00
										 |  |  |         df=12000.0/NFFT
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |         ia=nint(1000.0/df)
 | 
					
						
							|  |  |  |         ib=nint(2000.0/df)
 | 
					
						
							|  |  |  |         avemid=sum(s(ia:ib))/(ib-ia+1)
 | 
					
						
							|  |  |  |         do i=0,NH
 | 
					
						
							|  |  |  |            fil(i)=0.
 | 
					
						
							|  |  |  |            if(s(i).gt.0.0) then
 | 
					
						
							|  |  |  |               fil(i)=sqrt(avemid/s(i))
 | 
					
						
							|  |  |  |            endif
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-12 19:20:14 +00:00
										 |  |  | ! Default range is 240 - 4000 Hz.  For narrower filters, use frequencies
 | 
					
						
							|  |  |  | ! at which gain is -20 dB relative to 1500 Hz.
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |         ia=nint(240.0/df)
 | 
					
						
							| 
									
										
										
										
											2016-04-12 13:47:34 +00:00
										 |  |  |         ib=nint(4000.0/df)
 | 
					
						
							| 
									
										
										
										
											2016-04-12 19:20:14 +00:00
										 |  |  |         i0=nint(1500.0/df)
 | 
					
						
							|  |  |  |         do i=i0,ia,-1
 | 
					
						
							|  |  |  |            if(s(i)/s(i0).lt.0.01) exit
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  |         ia=i
 | 
					
						
							|  |  |  |         do i=i0,ib,1
 | 
					
						
							|  |  |  |            if(s(i)/s(i0).lt.0.01) exit
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  |         ib=i
 | 
					
						
							| 
									
										
										
										
											2016-04-12 13:47:34 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |         fac=fac0
 | 
					
						
							|  |  |  |         do i=ia,1,-1
 | 
					
						
							|  |  |  |            fac=fac*fac0
 | 
					
						
							|  |  |  |            fil(i)=fac*fil(i)
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |         fac=fac0
 | 
					
						
							|  |  |  |         do i=ib,NH
 | 
					
						
							|  |  |  |            fac=fac*fac0
 | 
					
						
							|  |  |  |            fil(i)=fac*fil(i)
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-12 19:20:14 +00:00
										 |  |  |         do iter=1,100                        !### ??? ###
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |            call smo121(fil,NH)
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-02-22 20:43:40 +00:00
										 |  |  |         do i=0,NH 
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |            filter(i)=-60.0
 | 
					
						
							|  |  |  |            if(s(i).gt.0.0) filter(i)=20.0*log10(fil(i))
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |         il=nint(NPOLYLOW/df)
 | 
					
						
							|  |  |  |         ih=nint(NPOLYHIGH/df)
 | 
					
						
							| 
									
										
										
										
											2017-02-22 20:43:40 +00:00
										 |  |  |         nfit=ih-il+1
 | 
					
						
							|  |  |  |         mode=0
 | 
					
						
							|  |  |  |         nterms=5
 | 
					
						
							|  |  |  |         do i=1,nfit
 | 
					
						
							|  |  |  |           xfit(i)=((i+il-1)*df-1500.0)/1000.0
 | 
					
						
							|  |  |  |           yfit(i)=fil(i+il-1)
 | 
					
						
							|  |  |  |           sigmay(i)=1.0
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  |         call polyfit(xfit,yfit,sigmay,nfit,nterms,mode,a,chisqr)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |         open(16,file=fname,status='unknown')
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |         write(16,1003) NPOLYLOW,NPOLYHIGH,nterms,a
 | 
					
						
							|  |  |  | 1003    format(3i5,5e25.16)
 | 
					
						
							| 
									
										
										
										
											2016-04-08 18:07:08 +00:00
										 |  |  |         do i=1,NH
 | 
					
						
							|  |  |  |            freq=i*df
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |            ref(i)=db(s(i)/avemid)
 | 
					
						
							| 
									
										
										
										
											2017-02-23 02:18:10 +00:00
										 |  |  |            write(16,1005) freq,s(i),ref(i),fil(i),filter(i)
 | 
					
						
							|  |  |  | 1005       format(f10.3,e12.3,f12.6,e12.3,f12.6)
 | 
					
						
							| 
									
										
										
										
											2016-04-08 18:07:08 +00:00
										 |  |  |         enddo
 | 
					
						
							|  |  |  |         close(16)
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |      return
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   if(buseref) then
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |      if(blastuse.neqv.buseref) then !just enabled so read filter
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |         fil=1.0
 | 
					
						
							| 
									
										
										
										
											2020-05-18 14:21:55 -04:00
										 |  |  |         open(16,file=fname,status='old',err=999)
 | 
					
						
							|  |  |  |         read(16,1003,err=20,end=999) ndummy,ndummy,nterms,a
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |         goto 30
 | 
					
						
							|  |  |  | 20      rewind(16)              !allow for old style refspec.dat with no header
 | 
					
						
							|  |  |  | 30      do i=1,NH
 | 
					
						
							| 
									
										
										
										
											2020-05-18 14:21:55 -04:00
										 |  |  |            read(16,1005,err=999,end=999) freq,s(i),ref(i),fil(i),filter(i)
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |         enddo
 | 
					
						
							| 
									
										
										
										
											2017-07-16 00:10:37 +00:00
										 |  |  | ! Make the filter causal for overlap and add.
 | 
					
						
							|  |  |  |         cx(0)=0.0
 | 
					
						
							|  |  |  |         cx(1:NH)=fil(1:NH)/NFFT
 | 
					
						
							| 
									
										
										
										
											2020-02-21 13:36:49 -05:00
										 |  |  |         call four2a(cx,NFFT,1,1,-1)
 | 
					
						
							| 
									
										
										
										
											2017-07-16 00:10:37 +00:00
										 |  |  |         x=cshift(x,-400)
 | 
					
						
							|  |  |  |         x(800:NH)=0.0
 | 
					
						
							|  |  |  |         call four2a(cx,NFFT,1,-1,0)
 | 
					
						
							|  |  |  |         cfil=cx
 | 
					
						
							| 
									
										
										
										
											2020-05-18 14:21:55 -04:00
										 |  |  |         close(16)
 | 
					
						
							| 
									
										
										
										
											2016-04-11 20:53:54 +00:00
										 |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2017-07-16 00:10:37 +00:00
										 |  |  | ! Use overlap and add method to apply causal reference filter.
 | 
					
						
							| 
									
										
										
										
											2017-07-15 15:43:41 +00:00
										 |  |  |      x(0:NH-1)=id2(1:NH)
 | 
					
						
							|  |  |  |      x(NH:NFFT-1)=0.0
 | 
					
						
							|  |  |  |      x=x/NFFT
 | 
					
						
							| 
									
										
										
										
											2020-02-21 13:36:49 -05:00
										 |  |  |      call four2a(cx,NFFT,1,-1,0)
 | 
					
						
							| 
									
										
										
										
											2017-07-16 00:10:37 +00:00
										 |  |  |      cx=cfil*cx
 | 
					
						
							| 
									
										
										
										
											2017-07-15 15:43:41 +00:00
										 |  |  |      call four2a(cx,NFFT,1,1,-1)
 | 
					
						
							|  |  |  |      x(0:NH-1)=x(0:NH-1)+xs    
 | 
					
						
							|  |  |  |      xs=x(NH:NFFT-1)
 | 
					
						
							|  |  |  |      id2(1:NH)=nint(x(0:NH-1))
 | 
					
						
							| 
									
										
										
										
											2016-04-08 18:07:08 +00:00
										 |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2017-02-23 16:21:26 +00:00
										 |  |  |   blastuse=buseref
 | 
					
						
							| 
									
										
										
										
											2020-05-18 14:21:55 -04:00
										 |  |  | 
 | 
					
						
							|  |  |  | 999 return
 | 
					
						
							| 
									
										
										
										
											2016-04-08 15:55:28 +00:00
										 |  |  | end subroutine refspectrum
 |