| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  | program fer65
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | ! End-to-end simulator for testing JT65.
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | ! Options 
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  | !  jt65sim                             jt65
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  | !----------------------------------------------------------------
 | 
					
						
							|  |  |  | !                                      -a aggressive
 | 
					
						
							|  |  |  | !  -d Doppler spread                   -d depth
 | 
					
						
							|  |  |  | !  -f Number of files                  -f freq
 | 
					
						
							|  |  |  | !  -m (sub)mode                        -m (sub)mode
 | 
					
						
							|  |  |  | !  -n number of generated sigs         -n ntrials
 | 
					
						
							|  |  |  | !  -t Time offset (s)                  -r robust sync
 | 
					
						
							|  |  |  | !  -p Do not seed random #s            -c mycall
 | 
					
						
							|  |  |  | !                                      -x hiscall
 | 
					
						
							|  |  |  | !                                      -g hisgrid
 | 
					
						
							|  |  |  | !                                      -X hinted-decode flags
 | 
					
						
							|  |  |  | !  -s S/N in 2500 Hz                   -s single-decode mode
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   implicit real*8 (a-h,o-z)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 |  |  |   real*8 s(7),sq(7)
 | 
					
						
							| 
									
										
										
										
											2016-03-18 20:17:17 +00:00
										 |  |  |   character arg*12,cmnd*100,decoded*22,submode*1,csync*1,f1*15,f2*15
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  |   character*12 outfile
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |   logical syncok
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   nargs=iargc()
 | 
					
						
							| 
									
										
										
										
											2016-03-21 17:23:49 +00:00
										 |  |  |   if(nargs.ne.7) then
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |      print*,'Usage:   fer65 submode fspread snr1 snr2 Navg  DS  iters'
 | 
					
						
							|  |  |  |      print*,'Example: fer65    C      3.0   -28  -12    8    1  1000'
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |      go to 999
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   call getarg(1,submode)
 | 
					
						
							|  |  |  |   call getarg(2,arg)
 | 
					
						
							|  |  |  |   read(arg,*) d
 | 
					
						
							|  |  |  |   call getarg(3,arg)
 | 
					
						
							|  |  |  |   read(arg,*) snr1
 | 
					
						
							|  |  |  |   call getarg(4,arg)
 | 
					
						
							|  |  |  |   read(arg,*) snr2
 | 
					
						
							|  |  |  |   call getarg(5,arg)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 17:23:49 +00:00
										 |  |  |   read(arg,*) navg
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |   call getarg(6,arg)
 | 
					
						
							|  |  |  |   read(arg,*) nds
 | 
					
						
							| 
									
										
										
										
											2016-03-21 17:23:49 +00:00
										 |  |  |   call getarg(7,arg)
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |   read(arg,*) iters
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-22 19:30:41 +00:00
										 |  |  |   write(outfile,1001) submode,d,navg,nds
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  | 1001 format(a1,f6.2,'_',i2.2,'_',i1)
 | 
					
						
							| 
									
										
										
										
											2016-03-22 19:30:41 +00:00
										 |  |  |   if(outfile(2:2).eq.' ') outfile(2:2)='0'
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  |   if(outfile(3:3).eq.' ') outfile(3:3)='0'
 | 
					
						
							| 
									
										
										
										
											2016-03-22 19:30:41 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |   ndepth=3
 | 
					
						
							|  |  |  |   if(navg.gt.1) ndepth=ndepth+16
 | 
					
						
							|  |  |  |   if(nds.ne.0) ndepth=ndepth+32
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  |   dfmax=3
 | 
					
						
							|  |  |  |   if(submode.eq.'b' .or. submode.eq.'B') dfmax=6
 | 
					
						
							|  |  |  |   if(submode.eq.'c' .or. submode.eq.'C') dfmax=11
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |   ntrials=1000
 | 
					
						
							|  |  |  |   naggressive=10
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-22 19:30:41 +00:00
										 |  |  |   open(20,file=outfile,status='unknown')
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |   open(21,file='fer65.21',status='unknown')
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  |   write(20,1000) submode,iters,ntrials,naggressive,d,ndepth,navg,nds
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  | 1000 format(/'JT65',a1,'  Iters:',i5,'  T:',i6,'  Aggr:',i3,  &
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  |           '  Dop:',f6.2,'  Depth:',i2,'  Navg:',i3,'  DS:',i2)
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |   write(20,1002) 
 | 
					
						
							| 
									
										
										
										
											2016-03-15 20:44:03 +00:00
										 |  |  | 1002 format(/'  dB  nsync ngood nbad     sync       dsnr        ',     &
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 |  |  |             'DT       Freq      Nsum     Width'/85('-'))
 | 
					
						
							| 
									
										
										
										
											2016-03-22 19:30:41 +00:00
										 |  |  |   flush(20)
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |   do isnr=0,20
 | 
					
						
							|  |  |  |      snr=snr1+isnr
 | 
					
						
							|  |  |  |      if(snr.gt.snr2) exit
 | 
					
						
							|  |  |  |      nsync=0
 | 
					
						
							|  |  |  |      ngood=0
 | 
					
						
							|  |  |  |      nbad=0
 | 
					
						
							|  |  |  |      s=0.
 | 
					
						
							|  |  |  |      sq=0.
 | 
					
						
							|  |  |  |      do iter=1,iters
 | 
					
						
							| 
									
										
										
										
											2016-03-21 17:23:49 +00:00
										 |  |  |         write(cmnd,1010) submode,d,snr,navg
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  | 1010    format('./jt65sim -n 1 -m ',a1,' -d',f7.2,' -s \\',f5.1,' -f',i3,' >devnull')
 | 
					
						
							| 
									
										
										
										
											2016-03-18 20:17:17 +00:00
										 |  |  |         call unlink('000000_????.wav')
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |         call system(cmnd)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 17:23:49 +00:00
										 |  |  |         if(navg.gt.1) then
 | 
					
						
							|  |  |  |            do i=navg,2,-1
 | 
					
						
							| 
									
										
										
										
											2016-03-18 20:17:17 +00:00
										 |  |  |               j=2*i-1
 | 
					
						
							|  |  |  |               write(f1,1011) i
 | 
					
						
							|  |  |  |               write(f2,1011) j
 | 
					
						
							|  |  |  | 1011          format('000000_',i4.4,'.wav')
 | 
					
						
							|  |  |  |               call rename(f1,f2)
 | 
					
						
							|  |  |  |            enddo
 | 
					
						
							|  |  |  |         endif
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |         call unlink('decoded.txt')
 | 
					
						
							|  |  |  |         call unlink('fort.13')
 | 
					
						
							|  |  |  |         isync=0
 | 
					
						
							|  |  |  |         nsnr=0
 | 
					
						
							|  |  |  |         dt=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |         nfreq=0
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |         ndrift=0
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |         nwidth=0
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |         cmnd='./jt65 -m A -a 10 -c K1ABC -f 1500 -n 1000 -d  5 -s 000000_????.wav > decoded.txt'
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |         cmnd(11:11)=submode
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:03:11 +00:00
										 |  |  |         write(cmnd(47:48),'(i2)') ndepth
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |         call system(cmnd)
 | 
					
						
							|  |  |  |         open(13,file='fort.13',status='old',err=20)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 17:23:49 +00:00
										 |  |  |         do i=1,navg
 | 
					
						
							| 
									
										
										
										
											2016-03-18 20:17:17 +00:00
										 |  |  |            read(13,1012) nutc,isync,nsnr,dt,nfreq,ndrift,nwidth,decoded,     &
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |              nft,nsum,nsmo
 | 
					
						
							| 
									
										
										
										
											2016-03-18 20:17:17 +00:00
										 |  |  | 1012       format(i4,i4,i5,f6.2,i5,i4,i3,1x,a22,5x,3i3)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 |  |  |            if(nft.gt.0) exit
 | 
					
						
							| 
									
										
										
										
											2016-03-18 20:17:17 +00:00
										 |  |  |         enddo
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |         close(13)
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |         syncok=abs(dt).lt.0.2 .and. float(abs(nfreq-1500)).lt.dfmax
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |         csync=' '
 | 
					
						
							|  |  |  |         if(syncok) csync='*'
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |         write(21,1014) nutc,isync,nsnr,dt,nfreq,ndrift,nwidth,     &
 | 
					
						
							| 
									
										
										
										
											2016-03-22 19:30:41 +00:00
										 |  |  |              nft,nsum,nsmo,csync,decoded(1:16),nft,nsum,nsmo
 | 
					
						
							|  |  |  | 1014    format(i4,i4,i5,f6.2,i5,i4,3x,4i3,1x,a1,1x,a16,i2,2i3)
 | 
					
						
							|  |  |  |         flush(21)
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |         if(syncok) then
 | 
					
						
							|  |  |  |            nsync=nsync+1
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |            s(1)=s(1) + isync
 | 
					
						
							|  |  |  |            sq(1)=sq(1) + isync*isync
 | 
					
						
							|  |  |  |            s(6)=s(6) + nwidth
 | 
					
						
							|  |  |  |            sq(6)=sq(6) + nwidth*nwidth
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |            if(decoded.eq.'K1ABC W9XYZ EN37      ') then
 | 
					
						
							|  |  |  |               ngood=ngood+1
 | 
					
						
							|  |  |  |               s(2)=s(2) + nsnr
 | 
					
						
							|  |  |  |               s(3)=s(3) + dt
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |               s(4)=s(4) + nfreq
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |               s(5)=s(5) + ndrift
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 |  |  |               s(7)=s(7) + nsum
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |               sq(2)=sq(2) + nsnr*nsnr
 | 
					
						
							|  |  |  |               sq(3)=sq(3) + dt*dt
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |               sq(4)=sq(4) + nfreq*nfreq
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |               sq(5)=sq(5) + ndrift*ndrift
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 |  |  |               sq(7)=sq(7) + nsum*nsum
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |            else if(decoded.ne.'                      ') then
 | 
					
						
							|  |  |  |               nbad=nbad+1
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |               print*,'Nbad:',nbad,decoded
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |            endif
 | 
					
						
							|  |  |  |         endif
 | 
					
						
							|  |  |  | 20      continue
 | 
					
						
							|  |  |  |         fsync=float(nsync)/iter
 | 
					
						
							|  |  |  |         fgood=float(ngood)/iter
 | 
					
						
							|  |  |  |         fbad=float(nbad)/iter
 | 
					
						
							| 
									
										
										
										
											2016-03-22 19:30:41 +00:00
										 |  |  |         write(*,1020) nint(snr),iter,isync,nsnr,dt,nfreq,ndrift,nwidth,fsync,  &
 | 
					
						
							|  |  |  |              fgood,fbad,decoded(1:16),nft,nsum,nsmo
 | 
					
						
							|  |  |  | 1020    format(i3,i5,i3,i4,f6.2,i5,i3,i3,2f6.3,f7.4,1x,a16,i2,2i3)
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |      enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |      if(nsync.ge.1) then
 | 
					
						
							|  |  |  |         xsync=s(1)/nsync
 | 
					
						
							|  |  |  |         xwidth=s(6)/nsync
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2016-03-22 19:30:41 +00:00
										 |  |  |      esync=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |      if(nsync.ge.2) then
 | 
					
						
							|  |  |  |         esync=sqrt(sq(1)/nsync - xsync**2)
 | 
					
						
							|  |  |  |         ewidth=sqrt(sq(6)/nsync - xwidth**2)
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |      if(ngood.ge.1) then
 | 
					
						
							|  |  |  |         xsnr=s(2)/ngood
 | 
					
						
							|  |  |  |         xdt=s(3)/ngood
 | 
					
						
							|  |  |  |         xfreq=s(4)/ngood
 | 
					
						
							|  |  |  |         xdrift=s(5)/ngood
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 |  |  |         xsum=s(7)/ngood
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |      endif
 | 
					
						
							|  |  |  |      if(ngood.ge.2) then
 | 
					
						
							|  |  |  |         esnr=sqrt(sq(2)/ngood - xsnr**2)
 | 
					
						
							|  |  |  |         edt=sqrt(sq(3)/ngood - xdt**2)
 | 
					
						
							|  |  |  |         efreq=sqrt(sq(4)/ngood - xfreq**2)
 | 
					
						
							|  |  |  |         edrift=sqrt(sq(5)/ngood - xdrift**2)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 |  |  |         esum=sqrt(sq(7)/ngood - xsum**2)
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |      endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |      dsnr=xsnr-snr
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |      dfreq=xfreq-1500.0
 | 
					
						
							| 
									
										
										
										
											2016-03-17 18:52:06 +00:00
										 |  |  |      if(ngood.eq.0) then
 | 
					
						
							|  |  |  |         dsnr=0.
 | 
					
						
							|  |  |  |         dfreq=0.
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |      write(20,1100) snr,nsync,ngood,nbad,xsync,esync,dsnr,esnr,  &
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 |  |  |           xdt,edt,dfreq,efreq,xsum,esum,xwidth,ewidth
 | 
					
						
							| 
									
										
										
										
											2016-03-28 18:52:12 +00:00
										 |  |  | 1100 format(f5.1,2i6,i4,2f6.1,f6.1,f5.1,f6.2,f5.2,6f5.1)
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |      flush(20)
 | 
					
						
							| 
									
										
										
										
											2016-03-23 13:55:40 +00:00
										 |  |  |      if(ngood.ge.int(0.99*iters)) exit
 | 
					
						
							| 
									
										
										
										
											2016-03-14 21:48:58 +00:00
										 |  |  |   enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | 999 end program fer65
 |