mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2024-11-22 04:11:16 -05:00
FST4/W: Disable envelope shaping at start and end of transmission when environment variable FST4_NOSHAPING=1. Works for fst4sim too.
This commit is contained in:
parent
afee4d9a28
commit
86b0affc56
@ -120,7 +120,7 @@ program fst4sim
|
|||||||
if(fspread.gt.0.0 .or. delay.ne.0.0) call watterson(c,nwave,NZ,fs,delay,fspread)
|
if(fspread.gt.0.0 .or. delay.ne.0.0) call watterson(c,nwave,NZ,fs,delay,fspread)
|
||||||
if(fspread.lt.0.0) call lorentzian_fading(c,nwave,fs,-fspread)
|
if(fspread.lt.0.0) call lorentzian_fading(c,nwave,fs,-fspread)
|
||||||
c=sig*c
|
c=sig*c
|
||||||
wave=real(c)
|
wave=aimag(c)
|
||||||
if(snrdb.lt.90) then
|
if(snrdb.lt.90) then
|
||||||
do i=1,nmax !Add gaussian noise at specified SNR
|
do i=1,nmax !Add gaussian noise at specified SNR
|
||||||
xnoise=gran()
|
xnoise=gran()
|
||||||
|
@ -1,91 +1,93 @@
|
|||||||
subroutine gen_fst4wave(itone,nsym,nsps,nwave,fsample,hmod,f0, &
|
subroutine gen_fst4wave(itone,nsym,nsps,nwave,fsample,hmod,f0, &
|
||||||
icmplx,cwave,wave)
|
icmplx,cwave,wave)
|
||||||
|
|
||||||
parameter(NTAB=65536)
|
use prog_args
|
||||||
real wave(nwave)
|
parameter(NTAB=65536)
|
||||||
complex cwave(nwave),ctab(0:NTAB-1)
|
real wave(nwave)
|
||||||
real, allocatable, save :: pulse(:)
|
complex cwave(nwave),ctab(0:NTAB-1)
|
||||||
real, allocatable :: dphi(:)
|
character(len=1) :: cvalue
|
||||||
integer hmod
|
real, allocatable, save :: pulse(:)
|
||||||
integer itone(nsym)
|
real, allocatable :: dphi(:)
|
||||||
logical first
|
integer hmod
|
||||||
data first/.true./
|
integer itone(nsym)
|
||||||
data nsps0/-99/
|
logical first, lshape
|
||||||
save first,twopi,dt,tsym,nsps0,ctab
|
data first/.true./
|
||||||
|
data nsps0/-99/
|
||||||
|
data lshape/.true./
|
||||||
|
save first,twopi,dt,tsym,nsps0,ctab,lshape
|
||||||
|
|
||||||
if(first) then
|
if(first) then
|
||||||
twopi=8.0*atan(1.0)
|
twopi=8.0*atan(1.0)
|
||||||
do i=0,NTAB-1
|
do i=0,NTAB-1
|
||||||
phi=i*twopi/NTAB
|
phi=i*twopi/NTAB
|
||||||
ctab(i)=cmplx(cos(phi),sin(phi))
|
ctab(i)=cmplx(cos(phi),sin(phi))
|
||||||
enddo
|
enddo
|
||||||
endif
|
call get_environment_variable("FST4_NOSHAPING",cvalue,nlen)
|
||||||
|
if(nlen.eq.1 .and. cvalue.eq."1") lshape=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
if(first.or.nsps.ne.nsps0) then
|
if(first.or.nsps.ne.nsps0) then
|
||||||
if(allocated(pulse)) deallocate(pulse)
|
if(allocated(pulse)) deallocate(pulse)
|
||||||
allocate(pulse(1:3*nsps))
|
allocate(pulse(1:3*nsps))
|
||||||
dt=1.0/fsample
|
dt=1.0/fsample
|
||||||
tsym=nsps/fsample
|
tsym=nsps/fsample
|
||||||
! Compute the smoothed frequency-deviation pulse
|
! Compute the smoothed frequency-deviation pulse
|
||||||
do i=1,3*nsps
|
do i=1,3*nsps
|
||||||
tt=(i-1.5*nsps)/real(nsps)
|
tt=(i-1.5*nsps)/real(nsps)
|
||||||
pulse(i)=gfsk_pulse(2.0,tt)
|
pulse(i)=gfsk_pulse(2.0,tt)
|
||||||
enddo
|
enddo
|
||||||
first=.false.
|
first=.false.
|
||||||
nsps0=nsps
|
nsps0=nsps
|
||||||
endif
|
endif
|
||||||
|
|
||||||
! Compute the smoothed frequency waveform.
|
! Compute the smoothed frequency waveform.
|
||||||
! Length = (nsym+2)*nsps samples, zero-padded
|
! Length = (nsym+2)*nsps samples, zero-padded
|
||||||
allocate( dphi(0:(nsym+2)*nsps-1) )
|
allocate( dphi(0:(nsym+2)*nsps-1) )
|
||||||
dphi_peak=twopi*hmod/real(nsps)
|
dphi_peak=twopi*hmod/real(nsps)
|
||||||
dphi=0.0
|
dphi=0.0
|
||||||
do j=1,nsym
|
do j=1,nsym
|
||||||
ib=(j-1)*nsps
|
ib=(j-1)*nsps
|
||||||
ie=ib+3*nsps-1
|
ie=ib+3*nsps-1
|
||||||
dphi(ib:ie) = dphi(ib:ie) + dphi_peak*pulse(1:3*nsps)*itone(j)
|
dphi(ib:ie) = dphi(ib:ie) + dphi_peak*pulse(1:3*nsps)*itone(j)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
! Calculate and insert the audio waveform
|
! Calculate and insert the audio waveform
|
||||||
phi=0.0
|
phi=0.0
|
||||||
dphi = dphi + twopi*(f0-1.5*hmod/tsym)*dt !Shift frequency up by f0
|
dphi = dphi + twopi*(f0-1.5*hmod/tsym)*dt !Shift frequency up by f0
|
||||||
if(icmplx.eq.0) wave=0.
|
if(icmplx.eq.0) wave=0.
|
||||||
if(icmplx.eq.1) cwave=0.
|
if(icmplx.eq.1) cwave=0.
|
||||||
k=0
|
k=0
|
||||||
do j=0,(nsym+2)*nsps-1
|
do j=nsps,(nsym+1)*nsps-1
|
||||||
k=k+1
|
k=k+1
|
||||||
i=phi*float(NTAB)/twopi
|
i=phi*float(NTAB)/twopi
|
||||||
i=iand(i,NTAB-1)
|
i=iand(i,NTAB-1)
|
||||||
if(icmplx.eq.0) then
|
if(icmplx.eq.0) then
|
||||||
wave(k)=real(ctab(i))
|
wave(k)=aimag(ctab(i))
|
||||||
else
|
else
|
||||||
cwave(k)=ctab(i)
|
cwave(k)=ctab(i)
|
||||||
endif
|
endif
|
||||||
phi=phi+dphi(j)
|
phi=phi+dphi(j)
|
||||||
if(phi.gt.twopi) phi=phi-twopi
|
if(phi.gt.twopi) phi=phi-twopi
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
! Compute the ramp-up and ramp-down symbols
|
! Compute the ramp-up and ramp-down symbols
|
||||||
kshift=nsps
|
if(icmplx.eq.0) then
|
||||||
if(icmplx.eq.0) then
|
if(lshape) then
|
||||||
wave(1:nsps)=0.0
|
wave(1:nsps/4)=wave(1:nsps/4) * &
|
||||||
wave(nsps+1:nsps+nsps/4)=wave(nsps+1:nsps+nsps/4) * &
|
(1.0-cos(twopi*(/(i,i=0,nsps/4-1)/)/real(nsps/2)))/2.0
|
||||||
(1.0-cos(twopi*(/(i,i=0,nsps/4-1)/)/real(nsps/2)))/2.0
|
k1=(nsym-1)*nsps+3*nsps/4+1
|
||||||
k1=nsym*nsps+3*nsps/4+1
|
wave(k1:k1+nsps/4)=wave(k1:k1+nsps/4) * &
|
||||||
wave((nsym+1)*nsps+1:)=0.0
|
(1.0+cos(twopi*(/(i,i=0,nsps/4)/)/real(nsps/2)))/2.0
|
||||||
wave(k1:k1+nsps/4)=wave(k1:k1+nsps/4) * &
|
endif
|
||||||
(1.0+cos(twopi*(/(i,i=0,nsps/4)/)/real(nsps/2)))/2.0
|
else
|
||||||
wave=cshift(wave,kshift)
|
if(lshape) then
|
||||||
else
|
cwave(1:nsps/4)=cwave(1:nsps/4) * &
|
||||||
cwave(1:nsps)=0.0
|
(1.0-cos(twopi*(/(i,i=0,nsps/4-1)/)/real(nsps/2)))/2.0
|
||||||
cwave(nsps+1:nsps+nsps/4)=cwave(nsps+1:nsps+nsps/4) * &
|
k1=(nsym-1)*nsps+3*nsps/4+1
|
||||||
(1.0-cos(twopi*(/(i,i=0,nsps/4-1)/)/real(nsps/2)))/2.0
|
cwave(k1:k1+nsps/4)=cwave(k1:k1+nsps/4) * &
|
||||||
k1=nsym*nsps+3*nsps/4+1
|
(1.0+cos(twopi*(/(i,i=0,nsps/4)/)/real(nsps/2)))/2.0
|
||||||
cwave((nsym+1)*nsps+1:)=0.0
|
endif
|
||||||
cwave(k1:k1+nsps/4)=cwave(k1:k1+nsps/4) * &
|
endif
|
||||||
(1.0+cos(twopi*(/(i,i=0,nsps/4)/)/real(nsps/2)))/2.0
|
|
||||||
cwave=cshift(cwave,kshift)
|
|
||||||
endif
|
|
||||||
|
|
||||||
return
|
return
|
||||||
end subroutine gen_fst4wave
|
end subroutine gen_fst4wave
|
||||||
|
Loading…
Reference in New Issue
Block a user