Enhance jt65sim to allow 11025 Hz rate, selectable base frequency and o/p gain offset.

Needs a review.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@8388 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
Bill Somerville 2018-01-01 22:02:31 +00:00
parent b76e5248df
commit d48fb58ffa

View File

@ -1,275 +1,293 @@
program jt65sim program jt65sim
! Generate simulated JT65 data for testing WSJT-X ! Generate simulated JT65 data for testing WSJT-X
use wavhdr use wavhdr
use packjt use packjt
use options use options
parameter (NMAX=54*12000) ! = 648,000 parameter (NMAX=54*12000) ! = 648,000 @12kHz
parameter (NFFT=10*65536,NH=NFFT/2) parameter (NFFT=10*65536,NH=NFFT/2)
type(hdr) h !Header for .wav file type(hdr) h !Header for .wav file
integer*2 iwave(NMAX) !Generated waveform integer*2 iwave(NMAX) !Generated waveform
integer*4 itone(126) !Channel symbols (values 0-65) integer*4 itone(126) !Channel symbols (values 0-65)
integer dgen(12) !Twelve 6-bit data symbols integer dgen(12) !Twelve 6-bit data symbols
integer sent(63) !RS(63,12) codeword integer sent(63) !RS(63,12) codeword
real*4 xnoise(NMAX) !Generated random noise real*4 xnoise(NMAX) !Generated random noise
real*4 dat(NMAX) !Generated real data real*4 dat(NMAX) !Generated real data
complex cdat(NMAX) !Generated complex waveform complex cdat(NMAX) !Generated complex waveform
complex cspread(0:NFFT-1) !Complex amplitude for Rayleigh fading complex cspread(0:NFFT-1) !Complex amplitude for Rayleigh fading
complex z complex z
real*8 f0,dt,twopi,phi,dphi,baud,fsample,freq,sps real*8 f0,dt,twopi,phi,dphi,baud,fsample,freq,sps
character msg*22,fname*11,csubmode*1,c,optarg*500,numbuf*32 character msg*22,fname*11,csubmode*1,c,optarg*500,numbuf*32
! character call1*5,call2*5 ! character call1*5,call2*5
logical :: display_help=.false.,seed_prngs=.true. logical :: display_help=.false.,seed_prngs=.true.
type (option) :: long_options(9) = [ & type (option) :: long_options(12) = [ &
option ('help',.false.,'h','Display this help message',''), & option ('help',.false.,'h','Display this help message',''), &
option ('sub-mode',.true.,'m','sub mode, default MODE=A','MODE'), & option ('sub-mode',.true.,'m','sub mode, default MODE=A','MODE'), &
option ('num-sigs',.true.,'n','number of signals per file, default SIGNALS=10','SIGNALS'), & option ('num-sigs',.true.,'n','number of signals per file, default SIGNALS=10','SIGNALS'), &
option ('doppler-spread',.true.,'d','Doppler spread, default SPREAD=0.0','SPREAD'), & option ('f0',.true.,'F','base frequency offset, default F0=1500.0','F0'), &
option ('time-offset',.true.,'t','Time delta, default SECONDS=0.0','SECONDS'), & option ('doppler-spread',.true.,'d','Doppler spread, default SPREAD=0.0','SPREAD'), &
option ('num-files',.true.,'f','Number of files to generate, default FILES=1','FILES'), & option ('time-offset',.true.,'t','Time delta, default SECONDS=0.0','SECONDS'), &
option ('no-prng-seed',.false.,'p','Do not seed PRNGs (use for reproducible tests)',''), & option ('num-files',.true.,'f','Number of files to generate, default FILES=1','FILES'), &
option ('strength',.true.,'s','S/N in dB (2500Hz reference b/w), default SNR=0','SNR'), & option ('no-prng-seed',.false.,'p','Do not seed PRNGs (use for reproducible tests)',''), &
option ('message',.true.,'M','Message text','Message') ] option ('strength',.true.,'s','S/N in dB (2500Hz reference b/w), default SNR=0','SNR'), &
option ('11025',.false.,'S','Generate at 11025Hz sample rate, default 12000Hz',''), &
integer nprc(126) !Sync pattern option ('gain-offset',.true.,'G','Gain offset in dB, default GAIN=0dB','GAIN'), &
data nprc/1,0,0,1,1,0,0,0,1,1,1,1,1,1,0,1,0,1,0,0, & option ('message',.true.,'M','Message text','Message') ]
0,1,0,1,1,0,0,1,0,0,0,1,1,1,0,0,1,1,1,1, &
0,1,1,0,1,1,1,1,0,0,0,1,1,0,1,0,1,0,1,1, & integer nprc(126) !Sync pattern
0,0,1,1,0,1,0,1,0,1,0,0,1,0,0,0,0,0,0,1, & data nprc/1,0,0,1,1,0,0,0,1,1,1,1,1,1,0,1,0,1,0,0, &
1,0,0,0,0,0,0,0,1,1,0,1,0,0,1,0,1,1,0,1, & 0,1,0,1,1,0,0,1,0,0,0,1,1,1,0,0,1,1,1,1, &
0,1,0,1,0,0,1,1,0,0,1,0,0,1,0,0,0,0,1,1, & 0,1,1,0,1,1,1,1,0,0,0,1,1,0,1,0,1,0,1,1, &
1,1,1,1,1,1/ 0,0,1,1,0,1,0,1,0,1,0,0,1,0,0,0,0,0,0,1, &
1,0,0,0,0,0,0,0,1,1,0,1,0,0,1,0,1,1,0,1, &
! Default parameters: 0,1,0,1,0,0,1,1,0,0,1,0,0,1,0,0,0,0,1,1, &
csubmode='A' 1,1,1,1,1,1/
mode65=1
nsigs=10 ! Default parameters:
fspread=0. csubmode='A'
xdt=0. mode65=1
snrdb=0. nsigs=10
nfiles=1 bf0=1500.
msg="K1ABC W9XYZ EN37" fspread=0.
xdt=0.
do snrdb=0.
call getopt('hm:n:d:t:f:ps:M:',long_options,c,optarg,narglen,nstat,noffset,nremain,.true.) nfiles=1
if( nstat .ne. 0 ) then nsample_rate=12000
exit gain_offset=0.
end if msg="K1ABC W9XYZ EN37"
select case (c)
case ('h') do
display_help = .true. call getopt('hm:n:F:d:t:f:ps:SG:M:',long_options,c,optarg,narglen,nstat,noffset,nremain,.true.)
case ('m') if( nstat .ne. 0 ) then
read (optarg(:narglen), *) csubmode exit
if(csubmode.eq.'A') mode65=1 end if
if(csubmode.eq.'B') mode65=2 select case (c)
if(csubmode.eq.'C') mode65=4 case ('h')
case ('n') display_help = .true.
read (optarg(:narglen), *,err=10) nsigs case ('m')
case ('d') read (optarg(:narglen), *) csubmode
read (optarg(:narglen), *,err=10) fspread if(csubmode.eq.'A') mode65=1
case ('t') if(csubmode.eq.'B') mode65=2
read (optarg(:narglen), *) numbuf if(csubmode.eq.'C') mode65=4
if (numbuf(1:1) == '\') then case ('n')
read (numbuf(2:), *,err=10) xdt read (optarg(:narglen), *,err=10) nsigs
else case ('F')
read (numbuf, *,err=10) xdt read (optarg(:narglen), *,err=10) bf0
end if case ('d')
case ('f') read (optarg(:narglen), *,err=10) fspread
read (optarg(:narglen), *,err=10) nfiles case ('t')
case ('p') read (optarg(:narglen), *) numbuf
seed_prngs=.false. if (numbuf(1:1) == '\') then !'\'
case ('s') read (numbuf(2:), *,err=10) xdt
read (optarg(:narglen), *) numbuf else
if (numbuf(1:1) == '\') then read (numbuf, *,err=10) xdt
read (numbuf(2:), *,err=10) snrdb end if
else case ('f')
read (numbuf, *,err=10) snrdb read (optarg(:narglen), *,err=10) nfiles
end if case ('p')
case ('M') seed_prngs=.false.
read (optarg(:narglen), '(A)',err=10) msg case ('s')
write(*,*) msg read (optarg(:narglen), *) numbuf
end select if (numbuf(1:1) == '\') then !'\'
cycle read (numbuf(2:), *,err=10) snrdb
10 display_help=.true. else
print *, 'Optional argument format error for option -', c read (numbuf, *,err=10) snrdb
end do end if
case ('S')
if(display_help .or. nstat.lt.0 .or. nremain.ge.1) then nsample_rate=11025
print *, '' case ('G')
print *, 'Usage: jt65sim [OPTIONS]' read (optarg(:narglen), *) numbuf
print *, '' if (numbuf(1:1) == '\') then !'\'
print *, ' Generate one or more simulated JT65 signals in .WAV file(s)' read (numbuf(2:), *, err=10) gain_offset
print *, '' else
print *, 'Example: jt65sim -m B -n 10 -d 0.2 -s \\-24.5 -t 0.0 -f 4' read (numbuf, *, err=10) gain_offset
print *, '' end if
print *, 'OPTIONS: NB Use \ (\\ on *nix shells) to escape -ve arguments' case ('M')
print *, '' read (optarg(:narglen), '(A)',err=10) msg
do i = 1, size (long_options) write(*,*) msg
call long_options(i) % print (6) end select
end do cycle
go to 999 10 display_help=.true.
endif print *, 'Optional argument format error for option -', c
end do
if (seed_prngs) then
call init_random_seed() ! seed Fortran RANDOM_NUMBER generator if(display_help .or. nstat.lt.0 .or. nremain.ge.1) then
call sgran() ! see C rand generator (used in gran) print *, ''
end if print *, 'Usage: jt65sim [OPTIONS]'
print *, ''
rms=100. print *, ' Generate one or more simulated JT65 signals in .WAV file(s)'
fsample=12000.d0 !Sample rate (Hz) print *, ''
dt=1.d0/fsample !Sample interval (s) print *, 'Example: jt65sim -m B -n 10 -d 0.2 -s \\-24.5 -t 0.0 -f 4'
twopi=8.d0*atan(1.d0) print *, ''
npts=54*12000 !Total samples in .wav file print *, 'OPTIONS: NB Use \ (\\ on *nix shells) to escape -ve arguments'
baud=11025.d0/4096.d0 !Keying rate print *, ''
sps=12000.d0/baud !Samples per symbol, at fsample=12000 Hz do i = 1, size (long_options)
nsym=126 !Number of channel symbols call long_options(i) % print (6)
h=default_header(12000,npts) end do
dfsig=2000.0/nsigs !Freq spacing between sigs in file (Hz) go to 999
endif
do ifile=1,nfiles !Loop over requested number of files
write(fname,1002) ifile !Output filename if (seed_prngs) then
1002 format('000000_',i4.4) call init_random_seed() ! seed Fortran RANDOM_NUMBER generator
open(10,file=fname//'.wav',access='stream',status='unknown') call sgran() ! see C rand generator (used in gran)
end if
xnoise=0.
cdat=0. rms=100. * 10. ** (gain_offset / 20.)
if(snrdb.lt.90) then
do i=1,npts fsample=nsample_rate !Sample rate (Hz)
xnoise(i)=gran() !Generate gaussian noise dt=1.d0/fsample !Sample interval (s)
enddo twopi=8.d0*atan(1.d0)
endif npts=54*nsample_rate !Total samples in .wav file
baud=11025.d0/4096.d0 !Keying rate
do isig=1,nsigs !Generate requested number of sigs sps=real(nsample_rate)/baud !Samples per symbol, at fsample=NSAMPLE_RATE Hz
if(mod(nsigs,2).eq.0) f0=1500.0 + dfsig*(isig-0.5-nsigs/2) nsym=126 !Number of channel symbols
if(mod(nsigs,2).eq.1) f0=1500.0 + dfsig*(isig-(nsigs+1)/2) h=default_header(nsample_rate,npts)
xsnr=snrdb dfsig=2000.0/nsigs !Freq spacing between sigs in file (Hz)
if(snrdb.eq.0.0) xsnr=-19 - isig
if(csubmode.eq.'B' .and. snrdb.eq.0.0) xsnr=-21 - isig do ifile=1,nfiles !Loop over requested number of files
if(csubmode.eq.'C' .and. snrdb.eq.0.0) xsnr=-21 - isig write(fname,1002) ifile !Output filename
1002 format('000000_',i4.4)
!### open(10,file=fname//'.wav',access='stream',status='unknown')
! call1="K1ABC"
! ic3=65+mod(isig-1,26) xnoise=0.
! ic2=65+mod((isig-1)/26,26) cdat=0.
! ic1=65 if(snrdb.lt.90) then
! call2="W9"//char(ic1)//char(ic2)//char(ic3) do i=1,npts
! write(msg,1010) call1,call2,nint(xsnr) xnoise(i)=gran() !Generate gaussian noise
!1010 format(a5,1x,a5,1x,i3.2) enddo
!### endif
call packmsg(msg,dgen,itype,.false.) !Pack message into 12 six-bit bytes
call rs_encode(dgen,sent) !Encode using RS(63,12) do isig=1,nsigs !Generate requested number of sigs
call interleave63(sent,1) !Interleave channel symbols if(mod(nsigs,2).eq.0) f0=bf0 + dfsig*(isig-0.5-nsigs/2)
call graycode65(sent,63,1) !Apply Gray code if(mod(nsigs,2).eq.1) f0=bf0 + dfsig*(isig-(nsigs+1)/2)
xsnr=snrdb
k=0 if(snrdb.eq.0.0) xsnr=-19 - isig
do j=1,nsym !Insert sync and data into itone() if(csubmode.eq.'B' .and. snrdb.eq.0.0) xsnr=-21 - isig
if(nprc(j).eq.0) then if(csubmode.eq.'C' .and. snrdb.eq.0.0) xsnr=-21 - isig
k=k+1
itone(j)=sent(k)+2 !###
else ! call1="K1ABC"
itone(j)=0 ! ic3=65+mod(isig-1,26)
endif ! ic2=65+mod((isig-1)/26,26)
enddo ! ic1=65
! call2="W9"//char(ic1)//char(ic2)//char(ic3)
bandwidth_ratio=2500.0/6000.0 ! write(msg,1010) call1,call2,nint(xsnr)
sig=sqrt(2*bandwidth_ratio)*10.0**(0.05*xsnr) !1010 format(a5,1x,a5,1x,i3.2)
if(xsnr.gt.90.0) sig=1.0 !###
write(*,1020) ifile,isig,f0,csubmode,xsnr,xdt,fspread,msg call packmsg(msg,dgen,itype,.false.) !Pack message into 12 six-bit bytes
1020 format(i4,i4,f10.3,2x,a1,2x,f5.1,f6.2,f5.1,1x,a22) call rs_encode(dgen,sent) !Encode using RS(63,12)
call interleave63(sent,1) !Interleave channel symbols
phi=0.d0 call graycode65(sent,63,1) !Apply Gray code
dphi=0.d0
k=12000 + xdt*12000 !Start audio at t = xdt + 1.0 s k=0
isym0=-99 do j=1,nsym !Insert sync and data into itone()
do i=1,npts !Add this signal into cdat() if(nprc(j).eq.0) then
isym=floor(i/sps)+1 k=k+1
if(isym.gt.nsym) exit itone(j)=sent(k)+2
if(isym.ne.isym0) then else
freq=f0 + itone(isym)*baud*mode65 itone(j)=0
dphi=twopi*freq*dt endif
isym0=isym enddo
endif
phi=phi + dphi bandwidth_ratio=2500.0/6000.0
if(phi.gt.twopi) phi=phi-twopi sig=sqrt(2*bandwidth_ratio)*10.0**(0.05*xsnr)
xphi=phi if(xsnr.gt.90.0) sig=1.0
z=cmplx(cos(xphi),sin(xphi)) write(*,1020) ifile,isig,f0,csubmode,xsnr,xdt,fspread,msg
k=k+1 1020 format(i4,i4,f10.3,2x,a1,2x,f5.1,f6.2,f5.1,1x,a22)
if(k.ge.1) cdat(k)=cdat(k) + sig*z
enddo phi=0.d0
enddo dphi=0.d0
k=nsample_rate + xdt*nsample_rate !Start audio at t = xdt + 1.0 s
if(fspread.ne.0) then !Apply specified Doppler spread isym0=-99
df=12000.0/nfft do i=1,npts !Add this signal into cdat()
twopi=8*atan(1.0) isym=floor(i/sps)+1
cspread(0)=1.0 if(isym.gt.nsym) exit
cspread(NH)=0. if(isym.ne.isym0) then
freq=f0 + itone(isym)*baud*mode65
! The following options were added 3/15/2016 to make the half-power tone dphi=twopi*freq*dt
! widths equal to the requested Doppler spread. (Previously we effectively isym0=isym
! used b=1.0 and Gaussian shape, which made the tones 1.665 times wider.) endif
! b=2.0*sqrt(log(2.0)) !Gaussian (before 3/15/2016) phi=phi + dphi
! b=2.0 !Lorenzian 3/15 - 3/27 if(phi.gt.twopi) phi=phi-twopi
b=6.0 !Lorenzian 3/28 onward xphi=phi
z=cmplx(cos(xphi),sin(xphi))
do i=1,NH k=k+1
f=i*df if(k.ge.1) cdat(k)=cdat(k) + sig*z
x=b*f/fspread enddo
z=0. enddo
a=0.
if(x.lt.3.0) then !Cutoff beyond x=3 if(fspread.ne.0) then !Apply specified Doppler spread
! a=sqrt(exp(-x*x)) !Gaussian df=real(nsample_rate)/nfft
a=sqrt(1.111/(1.0+x*x)-0.1) !Lorentzian twopi=8*atan(1.0)
call random_number(r1) cspread(0)=1.0
phi1=twopi*r1 cspread(NH)=0.
z=a*cmplx(cos(phi1),sin(phi1))
endif ! The following options were added 3/15/2016 to make the half-power tone
cspread(i)=z ! widths equal to the requested Doppler spread. (Previously we effectively
z=0. ! used b=1.0 and Gaussian shape, which made the tones 1.665 times wider.)
if(x.lt.50.0) then ! b=2.0*sqrt(log(2.0)) !Gaussian (before 3/15/2016)
call random_number(r2) ! b=2.0 !Lorenzian 3/15 - 3/27
phi2=twopi*r2 b=6.0 !Lorenzian 3/28 onward
z=a*cmplx(cos(phi2),sin(phi2))
endif do i=1,NH
cspread(NFFT-i)=z f=i*df
enddo x=b*f/fspread
z=0.
do i=0,NFFT-1 a=0.
f=i*df if(x.lt.3.0) then !Cutoff beyond x=3
if(i.gt.NH) f=(i-nfft)*df ! a=sqrt(exp(-x*x)) !Gaussian
s=real(cspread(i))**2 + aimag(cspread(i))**2 a=sqrt(1.111/(1.0+x*x)-0.1) !Lorentzian
! write(13,3000) i,f,s,cspread(i) call random_number(r1)
!3000 format(i5,f10.3,3f12.6) phi1=twopi*r1
enddo z=a*cmplx(cos(phi1),sin(phi1))
! s=real(cspread(0))**2 + aimag(cspread(0))**2 endif
! write(13,3000) 1024,0.0,s,cspread(0) cspread(i)=z
z=0.
call four2a(cspread,NFFT,1,1,1) !Transform to time domain if(x.lt.50.0) then
call random_number(r2)
sum=0. phi2=twopi*r2
do i=0,NFFT-1 z=a*cmplx(cos(phi2),sin(phi2))
p=real(cspread(i))**2 + aimag(cspread(i))**2 endif
sum=sum+p cspread(NFFT-i)=z
enddo enddo
avep=sum/NFFT
fac=sqrt(1.0/avep) do i=0,NFFT-1
cspread=fac*cspread !Normalize to constant avg power f=i*df
cdat=cspread(1:npts)*cdat !Apply Rayleigh fading if(i.gt.NH) f=(i-nfft)*df
s=real(cspread(i))**2 + aimag(cspread(i))**2
! do i=0,NFFT-1 ! write(13,3000) i,f,s,cspread(i)
! p=real(cspread(i))**2 + aimag(cspread(i))**2 !3000 format(i5,f10.3,3f12.6)
! write(14,3010) i,p,cspread(i) enddo
!3010 format(i8,3f12.6) ! s=real(cspread(0))**2 + aimag(cspread(0))**2
! enddo ! write(13,3000) 1024,0.0,s,cspread(0)
endif call four2a(cspread,NFFT,1,1,1) !Transform to time domain
dat=aimag(cdat) + xnoise !Add the generated noise sum=0.
fac=32767.0/nsigs do i=0,NFFT-1
if(snrdb.ge.90.0) iwave(1:npts)=nint(fac*dat(1:npts)) p=real(cspread(i))**2 + aimag(cspread(i))**2
if(snrdb.lt.90.0) iwave(1:npts)=nint(rms*dat(1:npts)) sum=sum+p
write(10) h,iwave(1:npts) !Save the .wav file enddo
close(10) avep=sum/NFFT
enddo fac=sqrt(1.0/avep)
cspread=fac*cspread !Normalize to constant avg power
999 end program jt65sim cdat(1:npts)=cspread(1:npts)*cdat(1:npts) !Apply Rayleigh fading
! do i=0,NFFT-1
! p=real(cspread(i))**2 + aimag(cspread(i))**2
! write(14,3010) i,p,cspread(i)
!3010 format(i8,3f12.6)
! enddo
endif
dat=aimag(cdat) + xnoise !Add the generated noise
fac=32767.0/nsigs
if(snrdb.ge.90.0) iwave(1:npts)=nint(fac*dat(1:npts))
if(snrdb.lt.90.0) iwave(1:npts)=nint(rms*dat(1:npts))
write(10) h,iwave(1:npts) !Save the .wav file
close(10)
enddo
999 end program jt65sim