2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								program ft4sim_mult
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! Generate simulated signals for experimental "FT4" mode 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  use wavhdr
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  use packjt77
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  include 'ft4_params.f90'               !FT4 protocol constants
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  parameter (NWAVE=NN*NSPS)
							 | 
						
					
						
							
								
									
										
										
										
											2019-05-23 14:06:00 -04:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  parameter (NZZ=72576)                  !Length of .wav file (21*3456)
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  type(hdr) h                            !Header for .wav file
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  character arg*12,fname*17,cjunk*4
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  character msg37*37,msgsent37*37,c77*77
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-18 14:15:24 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  complex cwave0((NN+2)*NSPS)
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-31 16:07:07 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  real wave0((NN+2)*NSPS)
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  real wave(NZZ)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  real tmp(NZZ)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer itone(NN)
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-18 14:16:39 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer*1 msgbits(77)
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer*2 iwave(NZZ)                  !Generated full-length waveform
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! Get command-line argument(s)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  nargs=iargc()
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(nargs.ne.2) then
							 | 
						
					
						
							
								
									
										
										
										
											2019-02-27 09:34:40 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     print*,'Usage:    ft4sim_mult nsigs nfiles'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     print*,'Example:  ft4sim_mult  20     8 '
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     go to 999
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  call getarg(1,arg)
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-03 11:48:57 -04:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  read(arg,*) nsigs               !Number of signals
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  call getarg(2,arg)
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-03 11:48:57 -04:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  read(arg,*) nfiles              !Number of files
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  twopi=8.0*atan(1.0)
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-03 11:48:57 -04:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  fs=12000.0                      !Sample rate (Hz)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  dt=1.0/fs                       !Sample interval (s)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  hmod=1.0                        !Modulation index (0.5 is MSK, 1.0 is FSK)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  tt=NSPS*dt                      !Duration of unsmoothed symbols (s)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  baud=1.0/tt                     !Keying rate (baud)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  txt=NZ*dt                       !Transmission length (s) without ramp up/down
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  bandwidth_ratio=2500.0/(fs/2.0)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  txt=NN*NSPS/12000.0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  open(10,file='messages.txt',status='old',err=998)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  do ifile=1,nfiles
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								1    read(10,1001,end=999) cjunk,n
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								1001 format(a4,i2)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     if(cjunk.ne.'File' .or. n.ne.ifile) go to 1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     wave=0.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     write(fname,1002) ifile
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								1002 format('000000_',i6.6,'.wav')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do isig=1,nsigs
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        read(10,1003,end=100) cjunk,isnr,xdt0,ifreq,msg37
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								1003    format(a4,30x,i3,f5.1,i5,1x,a37)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(cjunk.eq.'File') go to 100
							 | 
						
					
						
							
								
									
										
										
										
											2019-05-23 14:06:00 -04:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        if(isnr.lt.-17) isnr=-17
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        f0=ifreq*960.0/576.0
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        call random_number(r)
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-03 11:48:57 -04:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        xdt=r-0.5
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! Source-encode, then get itone()
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        i3=-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        n3=-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        call pack77(msg37,i3,n3,c77)
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-18 14:16:39 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        call genft4(msg37,0,msgsent37,msgbits,itone)
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-31 16:07:07 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        nwave0=(NN+2)*NSPS
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-18 14:15:24 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        icmplx=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        call gen_ft4wave(itone,NN,NSPS,12000.0,f0,cwave0,wave0,icmplx,nwave0)
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2019-04-03 12:45:38 -04:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        k0=nint((xdt+0.5)/dt)
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-31 16:07:07 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        if(k0.lt.1) k0=1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        tmp(:k0-1)=0.0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        tmp(k0:k0+nwave0-1)=wave0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        tmp(k0+nwave0:)=0.0
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								 ! Insert this signal into wave() array
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        sig=sqrt(2*bandwidth_ratio) * 10.0**(0.05*isnr)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        wave=wave + sig*tmp
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-31 14:06:05 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        write(*,1100) fname(1:13),isig,isnr,xdt,nint(f0),msg37
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								1100    format(a13,i4,i5,f5.1,i6,2x,a37)
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     enddo   ! isig
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								   
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								100  backspace 10
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-31 11:37:54 -05:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do i=1,NZZ                   !Add gaussian noise at specified SNR
							 | 
						
					
						
							
								
									
										
										
										
											2019-01-30 15:33:47 -05:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        xnoise=gran()
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        wave(i)=wave(i) + xnoise
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     gain=30.0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     wave=gain*wave
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     if(any(abs(wave).gt.32767.0)) print*,"Warning - data will be clipped."
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     iwave=nint(wave)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     h=default_header(12000,NZZ)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     open(12,file=fname,status='unknown',access='stream')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     write(12) h,iwave                !Save to *.wav file
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     close(12)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     print*,' '
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo      ! ifile
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  go to 999
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								998 print*,'Cannot open file "messages.txt"'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								999 end program ft4sim_mult
							 |