| 
									
										
										
										
											2022-06-22 14:34:50 -04:00
										 |  |  | subroutine avecho(id2,ndop,nfrit,nauto,nqual,f1,xlevel,snrdb,db_err,  &
 | 
					
						
							|  |  |  |      dfreq,width)
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |   integer TXLENGTH
 | 
					
						
							|  |  |  |   parameter (TXLENGTH=27648)           !27*1024
 | 
					
						
							|  |  |  |   parameter (NFFT=32768,NH=NFFT/2)
 | 
					
						
							| 
									
										
										
										
											2015-06-11 14:38:31 +00:00
										 |  |  |   parameter (NZ=4096)
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   integer*2 id2(34560)                 !Buffer for Rx data
 | 
					
						
							| 
									
										
										
										
											2015-06-11 14:38:31 +00:00
										 |  |  |   real sa(NZ)      !Avg spectrum relative to initial Doppler echo freq
 | 
					
						
							|  |  |  |   real sb(NZ)      !Avg spectrum with Dither and changing Doppler removed
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   integer nsum       !Number of integrations
 | 
					
						
							|  |  |  |   real dop0          !Doppler shift for initial integration (Hz)
 | 
					
						
							| 
									
										
										
										
											2015-06-09 19:04:21 +00:00
										 |  |  |   real dop           !Doppler shift for current integration (Hz)
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   real s(8192)
 | 
					
						
							|  |  |  |   real x(NFFT)
 | 
					
						
							|  |  |  |   integer ipkv(1)
 | 
					
						
							| 
									
										
										
										
											2022-04-22 15:34:12 -04:00
										 |  |  |   logical ex
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   complex c(0:NH)
 | 
					
						
							|  |  |  |   equivalence (x,c),(ipk,ipkv)
 | 
					
						
							| 
									
										
										
										
											2015-06-11 14:38:31 +00:00
										 |  |  |   common/echocom/nclearave,nsum,blue(NZ),red(NZ)
 | 
					
						
							| 
									
										
										
										
											2022-06-22 14:34:50 -04:00
										 |  |  |   common/echocom2/fspread_self,fspread_dx
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   save dop0,sa,sb
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2022-06-22 14:34:50 -04:00
										 |  |  |   fspread=fspread_dx                !### Use the predicted Doppler spread ###
 | 
					
						
							|  |  |  |   if(nauto.eq.1) fspread=fspread_self
 | 
					
						
							| 
									
										
										
										
											2022-04-22 15:34:12 -04:00
										 |  |  |   inquire(file='fspread.txt',exist=ex)
 | 
					
						
							|  |  |  |   if(ex) then
 | 
					
						
							|  |  |  |      open(39,file='fspread.txt',status='old')
 | 
					
						
							|  |  |  |      read(39,*) fspread
 | 
					
						
							|  |  |  |      close(39)
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2022-06-22 14:34:50 -04:00
										 |  |  |   fspread=min(max(0.1,fspread),700.0)
 | 
					
						
							| 
									
										
										
										
											2022-04-22 15:34:12 -04:00
										 |  |  |   width=fspread
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   dop=ndop
 | 
					
						
							|  |  |  |   sq=0.
 | 
					
						
							|  |  |  |   do i=1,TXLENGTH
 | 
					
						
							|  |  |  |      x(i)=id2(i)
 | 
					
						
							|  |  |  |      sq=sq + x(i)*x(i)
 | 
					
						
							|  |  |  |   enddo
 | 
					
						
							| 
									
										
										
										
											2015-06-09 19:04:21 +00:00
										 |  |  |   xlevel=10.0*log10(sq/TXLENGTH)
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |   if(nclearave.ne.0) nsum=0
 | 
					
						
							|  |  |  |   if(nsum.eq.0) then
 | 
					
						
							| 
									
										
										
										
											2015-06-09 00:43:07 +00:00
										 |  |  |      dop0=dop                             !Remember the initial Doppler
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |      sa=0.                                !Clear the average arrays
 | 
					
						
							|  |  |  |      sb=0.
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   x(TXLENGTH+1:)=0.
 | 
					
						
							|  |  |  |   x=x/TXLENGTH
 | 
					
						
							|  |  |  |   call four2a(x,NFFT,1,-1,0)
 | 
					
						
							|  |  |  |   df=12000.0/NFFT
 | 
					
						
							|  |  |  |   do i=1,8192                             !Get spectrum 0 - 3 kHz
 | 
					
						
							|  |  |  |      s(i)=real(c(i))**2 + aimag(c(i))**2
 | 
					
						
							|  |  |  |   enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   fnominal=1500.0           !Nominal audio frequency w/o doppler or dither
 | 
					
						
							|  |  |  |   ia=nint((fnominal+dop0-nfrit)/df)
 | 
					
						
							| 
									
										
										
										
											2015-06-09 00:43:07 +00:00
										 |  |  |   ib=nint((f1+dop-nfrit)/df)
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   if(ia.lt.600 .or. ib.lt.600) go to 900
 | 
					
						
							|  |  |  |   if(ia.gt.7590 .or. ib.gt.7590) go to 900
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   nsum=nsum+1
 | 
					
						
							| 
									
										
										
										
											2015-06-11 14:38:31 +00:00
										 |  |  |   do i=1,NZ
 | 
					
						
							| 
									
										
										
										
											2015-06-09 16:15:35 +00:00
										 |  |  |      sa(i)=sa(i) + s(ia+i-2048)    !Center at initial doppler freq
 | 
					
						
							|  |  |  |      sb(i)=sb(i) + s(ib+i-2048)    !Center at expected echo freq
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   enddo
 | 
					
						
							| 
									
										
										
										
											2022-04-22 15:34:12 -04:00
										 |  |  |   call echo_snr(sa,sb,fspread,blue,red,snrdb,db_err,dfreq,snr_detect)
 | 
					
						
							|  |  |  |   nqual=snr_detect-2
 | 
					
						
							|  |  |  |   if(nqual.lt.0) nqual=0
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   if(nqual.gt.10) nqual=10
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | ! Scale for plotting
 | 
					
						
							| 
									
										
										
										
											2022-04-22 15:34:12 -04:00
										 |  |  |   redmax=maxval(red)
 | 
					
						
							|  |  |  |   fac=10.0/max(redmax,10.0)
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   blue=fac*blue
 | 
					
						
							|  |  |  |   red=fac*red
 | 
					
						
							| 
									
										
										
										
											2022-04-22 15:34:12 -04:00
										 |  |  |   nsmo=max(0.0,0.25*width/df)
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   do i=1,nsmo
 | 
					
						
							| 
									
										
										
										
											2015-06-11 14:38:31 +00:00
										 |  |  |      call smo121(red,NZ)
 | 
					
						
							|  |  |  |      call smo121(blue,NZ)
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  |   enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2022-04-22 15:34:12 -04:00
										 |  |  | !  write(*,3001) snrdb,db_err,dfreq,snr_detect,redmax,nqual,nsmo,nclearave,nsum
 | 
					
						
							|  |  |  | !3001 format('A',5f10.1,4i4)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-06-09 16:15:35 +00:00
										 |  |  | 900  return
 | 
					
						
							| 
									
										
										
										
											2015-06-08 19:42:20 +00:00
										 |  |  | end subroutine avecho
 |