| 
									
										
										
										
											2019-04-12 17:11:26 -05:00
										 |  |  | subroutine gen_ft8wave(itone,nsym,nsps,bt,fsample,f0,cwave,wave,icmplx,nwave)
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  | !
 | 
					
						
							|  |  |  | ! generate ft8 waveform using Gaussian-filtered frequency pulses.
 | 
					
						
							|  |  |  | !
 | 
					
						
							| 
									
										
										
										
											2020-03-03 12:40:27 -05:00
										 |  |  |   use timer_module, only: timer
 | 
					
						
							|  |  |  |   parameter(MAX_SECONDS=20,NTAB=65536)
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  |   real wave(nwave)
 | 
					
						
							| 
									
										
										
										
											2020-03-03 12:40:27 -05:00
										 |  |  |   complex cwave(nwave),ctab(0:NTAB-1)
 | 
					
						
							| 
									
										
										
										
											2019-02-22 13:39:39 -05:00
										 |  |  |   real pulse(23040)
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:56:21 -06:00
										 |  |  |   real dphi(0:(nsym+2)*nsps-1)
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  |   integer itone(nsym)
 | 
					
						
							| 
									
										
										
										
											2021-10-28 11:47:00 -04:00
										 |  |  |   data fchk0/0.0/
 | 
					
						
							|  |  |  |   save pulse,twopi,dt,hmod,fchk0,ctab
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-04-12 17:11:26 -05:00
										 |  |  |   ibt=nint(10*bt)
 | 
					
						
							| 
									
										
										
										
											2021-10-28 11:47:00 -04:00
										 |  |  |   fchk=nsym+nsps+bt+fsample
 | 
					
						
							|  |  |  |   if(fchk.ne.fchk0) then
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  |      twopi=8.0*atan(1.0)
 | 
					
						
							|  |  |  |      dt=1.0/fsample
 | 
					
						
							|  |  |  |      hmod=1.0
 | 
					
						
							|  |  |  | ! Compute the frequency-smoothing pulse
 | 
					
						
							|  |  |  |      do i=1,3*nsps
 | 
					
						
							|  |  |  |         tt=(i-1.5*nsps)/real(nsps)
 | 
					
						
							|  |  |  |         pulse(i)=gfsk_pulse(bt,tt)
 | 
					
						
							|  |  |  |      enddo
 | 
					
						
							| 
									
										
										
										
											2020-03-03 12:40:27 -05:00
										 |  |  |      do i=0,NTAB-1
 | 
					
						
							|  |  |  |         phi=i*twopi/NTAB
 | 
					
						
							|  |  |  |         ctab(i)=cmplx(cos(phi),sin(phi))
 | 
					
						
							|  |  |  |      enddo
 | 
					
						
							| 
									
										
										
										
											2021-10-28 11:47:00 -04:00
										 |  |  |      fchk0=fchk
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | ! Compute the smoothed frequency waveform.
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:03:43 -06:00
										 |  |  | ! Length = (nsym+2)*nsps samples, first and last symbols extended 
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  |   dphi_peak=twopi*hmod/real(nsps)
 | 
					
						
							|  |  |  |   dphi=0.0 
 | 
					
						
							|  |  |  |   do j=1,nsym         
 | 
					
						
							|  |  |  |      ib=(j-1)*nsps
 | 
					
						
							|  |  |  |      ie=ib+3*nsps-1
 | 
					
						
							|  |  |  |      dphi(ib:ie) = dphi(ib:ie) + dphi_peak*pulse(1:3*nsps)*itone(j)
 | 
					
						
							|  |  |  |   enddo
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:03:43 -06:00
										 |  |  | ! Add dummy symbols at beginning and end with tone values equal to 1st and last symbol, respectively
 | 
					
						
							|  |  |  |   dphi(0:2*nsps-1)=dphi(0:2*nsps-1)+dphi_peak*itone(1)*pulse(nsps+1:3*nsps)
 | 
					
						
							|  |  |  |   dphi(nsym*nsps:(nsym+2)*nsps-1)=dphi(nsym*nsps:(nsym+2)*nsps-1)+dphi_peak*itone(nsym)*pulse(1:2*nsps)
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  | ! Calculate and insert the audio waveform
 | 
					
						
							|  |  |  |   phi=0.0
 | 
					
						
							| 
									
										
										
										
											2020-03-03 12:40:27 -05:00
										 |  |  |   dphi = dphi + twopi*f0*dt                      !Shift frequency up by f0
 | 
					
						
							| 
									
										
										
										
											2020-06-10 08:22:14 -05:00
										 |  |  |   if(icmplx .eq. 0) wave=0.
 | 
					
						
							| 
									
										
										
										
											2020-03-03 12:40:27 -05:00
										 |  |  |   if(icmplx .ne. 0) cwave=0. !Avoid writing to memory we may not have access to
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   call timer('gen_loop',0)
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  |   k=0
 | 
					
						
							| 
									
										
										
										
											2020-03-03 12:40:27 -05:00
										 |  |  |   do j=nsps,nsps+nwave-1                         !Don't include dummy symbols
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  |      k=k+1
 | 
					
						
							| 
									
										
										
										
											2019-02-22 13:39:39 -05:00
										 |  |  |      if(icmplx.eq.0) then
 | 
					
						
							|  |  |  |         wave(k)=sin(phi)
 | 
					
						
							|  |  |  |      else
 | 
					
						
							| 
									
										
										
										
											2020-03-03 12:40:27 -05:00
										 |  |  |         i=phi*float(NTAB)/twopi
 | 
					
						
							|  |  |  |         cwave(k)=ctab(i)
 | 
					
						
							| 
									
										
										
										
											2019-02-22 13:39:39 -05:00
										 |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  |      phi=mod(phi+dphi(j),twopi)
 | 
					
						
							|  |  |  |   enddo
 | 
					
						
							| 
									
										
										
										
											2020-03-03 12:40:27 -05:00
										 |  |  |   call timer('gen_loop',1)
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:03:43 -06:00
										 |  |  | ! Apply envelope shaping to the first and last symbols
 | 
					
						
							|  |  |  |   nramp=nint(nsps/8.0)
 | 
					
						
							| 
									
										
										
										
											2019-02-22 13:39:39 -05:00
										 |  |  |   if(icmplx.eq.0) then
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:03:43 -06:00
										 |  |  |      wave(1:nramp)=wave(1:nramp) *                                          &
 | 
					
						
							|  |  |  |           (1.0-cos(twopi*(/(i,i=0,nramp-1)/)/(2.0*nramp)))/2.0
 | 
					
						
							|  |  |  |      k1=nsym*nsps-nramp+1
 | 
					
						
							|  |  |  |      wave(k1:k1+nramp-1)=wave(k1:k1+nramp-1) *                              &
 | 
					
						
							|  |  |  |           (1.0+cos(twopi*(/(i,i=0,nramp-1)/)/(2.0*nramp)))/2.0
 | 
					
						
							| 
									
										
										
										
											2019-02-22 13:39:39 -05:00
										 |  |  |   else
 | 
					
						
							| 
									
										
										
										
											2019-02-25 15:03:43 -06:00
										 |  |  |      cwave(1:nramp)=cwave(1:nramp) *                                        &
 | 
					
						
							|  |  |  |           (1.0-cos(twopi*(/(i,i=0,nramp-1)/)/(2.0*nramp)))/2.0
 | 
					
						
							|  |  |  |      k1=nsym*nsps-nramp+1
 | 
					
						
							|  |  |  |      cwave(k1:k1+nramp-1)=cwave(k1:k1+nramp-1) *                            &
 | 
					
						
							|  |  |  |           (1.0+cos(twopi*(/(i,i=0,nramp-1)/)/(2.0*nramp)))/2.0
 | 
					
						
							| 
									
										
										
										
											2019-02-22 13:39:39 -05:00
										 |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2019-02-21 15:48:02 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  |   return
 | 
					
						
							|  |  |  | end subroutine gen_ft8wave
 |