Merge branch 'sfox5b' of bitbucket.org:k1jt/wsjtx into sfox5b

This commit is contained in:
Joe Taylor 2024-09-21 15:33:02 -04:00
commit 77e93a81e1
5 changed files with 284 additions and 2 deletions

View File

@ -618,6 +618,9 @@ set (wsjt_FSRCS
lib/superfox/sfrx_sub.f90
lib/superfox/sftx_sub.f90
lib/superfox/twkfreq2.f90
lib/superfox/sfox_gen_gfsk.f90
lib/superfox/ran1.f90
lib/superfox/sfoxsim.f90
)
# temporary workaround for a gfortran v7.3 ICE on Fedora 27 64-bit
@ -1254,6 +1257,9 @@ target_link_libraries (echosim wsjt_fort wsjt_cxx)
add_executable (ft8sim lib/ft8/ft8sim.f90)
target_link_libraries (ft8sim wsjt_fort wsjt_cxx)
add_executable (sfoxsim lib/superfox/sfoxsim.f90)
target_link_libraries (sfoxsim wsjt_fort wsjt_cxx)
#add_executable (sfrx lib/superfox/sfrx.f90)
#target_link_libraries (sfrx wsjt_fort wsjt_cxx)

View File

@ -217,9 +217,9 @@ subroutine remove_tone(c0,fsync)
enddo
sigma=sqrt(s2/s0)*df
! write(61,*) 'frequency, spectral width ',f2,sigma
! write(*,*) 'frequency, spectral width ',f2,sigma
if(sigma .gt. 2.5) go to 999
! write(61,*) 'remove_tone - frequency: ',f2
! write(*,*) 'remove_tone - frequency: ',f2
dt=1.0/fsample
do i=1, NMAX

28
lib/superfox/ran1.f90 Normal file
View File

@ -0,0 +1,28 @@
FUNCTION ran1(idum)
INTEGER idum,IA,IM,IQ,IR,NTAB,NDIV
REAL ran1,AM,EPS,RNMX
PARAMETER (IA=16807,IM=2147483647,AM=1./IM,IQ=127773,IR=2836, &
NTAB=32,NDIV=1+(IM-1)/NTAB,EPS=1.2e-7,RNMX=1.-EPS)
INTEGER j,k,iv(NTAB),iy
SAVE iv,iy
DATA iv /NTAB*0/, iy /0/
if (idum.le.0.or.iy.eq.0) then
idum=max(-idum,1)
do j=NTAB+8,1,-1
k=idum/IQ
idum=IA*(idum-k*IQ)-IR*k
if (idum.lt.0) idum=idum+IM
if (j.le.NTAB) iv(j)=idum
enddo
iy=iv(1)
endif
k=idum/IQ
idum=IA*(idum-k*IQ)-IR*k
if (idum.lt.0) idum=idum+IM
j=1+iy/NDIV
iy=iv(j)
iv(j)=idum
ran1=min(AM*iy,RNMX)
return
END FUNCTION ran1

View File

@ -0,0 +1,86 @@
subroutine sfox_gen_gfsk(idat,f0,isync,itone,cdat)
parameter (NSPS=1024)
parameter (NDS=151)
parameter (NN=127) !NN = number of code symbols
parameter (NS=24) !NS = number of sync symbols
parameter (NMAX=15*12000)
parameter (NPTS=(NDS+2)*NSPS) !# of samples in waveform at 12000 samples/sec
parameter (BT=8) !GFSK time-bandwidth product
complex cdat(NMAX)
complex w, wstep
integer idat(NN)
integer isync(NS)
integer itone(NDS)
real*8 dt,twopi,phi,dphi_peak
real*8 dphi(0:NPTS-1)
real pulse(3*NSPS)
logical first/.true./
save first,twopi,dt,hmod,dphi_peak,pulse
if(first) then
twopi=8.d0*atan(1.0)
fsample=12000.0
dt=1.0/fsample
hmod=1.0
dphi_peak=twopi*hmod/real(NSPS)
do i=1,3*NSPS
tt=(i-1.5*NSPS)/real(NSPS)
pulse(i)=gfsk_pulse(BT,tt)
enddo
first=.false.
endif
wave=0.
! Create the itone sequence: data symbols and interspersed sync symbols
j=1
k=0
do i=1,NDS
if(j.le.NS .and. i.eq.isync(j)) then
if(j.lt.NS) j=j+1 !Index for next sync symbol
itone(i)=0 !Insert sync symbol at tone 0
else
k=k+1
itone(i)=idat(k) + 1 !Symbol value 0 is transmitted at tone 1, etc.
endif
enddo
! Generate the SuperFox waveform.
dphi=0.d0
do j=1,NDS
ib=(j-1)*NSPS
ie=ib+3*NSPS-1
dphi(ib:ie)=dphi(ib:ie)+dphi_peak*pulse(1:3*NSPS)*itone(j)
enddo
dphi(0:2*NSPS-1)=dphi(0:2*NSPS-1)+dphi_peak*itone(1)*pulse(NSPS+1:3*NSPS)
dphi(NDS*NSPS:(NDS+2)*NSPS-1)=dphi(NDS*NSPS:(NDS+2)*NSPS-1)+dphi_peak*itone(NDS)*pulse(1:2*NSPS)
phi=0.d0
dphi=dphi+twopi*f0*dt
k=0
do j=1,NSPS*(NDS+2)-1
k=k+1
cdat(k)=cmplx(cos(phi),sin(phi))
phi=phi+dphi(j)
enddo
! Add raised cosine ramps at the beginning and end of the waveform.
! Since the modulator expects an integral number of symbols, dummy
! symbols are added to the beginning and end of the waveform to
! hold the ramps. All but nramp of the samples in each dummy
! symbol will be zero.
nramp=NSPS/BT
cdat(1:NSPS-nramp)=cmplx(0.0,0.0)
cdat(NSPS-nramp+1:NSPS)=cdat(NSPS-nramp+1:NSPS) * &
(1.0-cos(twopi*(/(i,i=0,nramp-1)/)/(2.0*nramp)))/2.0
k1=(NDS+1)*NSPS+1
cdat(k1:k1+nramp-1)=cdat(k1:k1+nramp-1) * &
(1.0+cos(twopi*(/(i,i=0,nramp-1)/)/(2.0*nramp)))/2.0
cdat(k1+nramp:NPTS)=0.0
return
end subroutine sfox_gen_gfsk

162
lib/superfox/sfoxsim.f90 Normal file
View File

@ -0,0 +1,162 @@
program sfoxsim
! - Generate complex-valued SuperFox waveform, cdat.
! - Pass cdat through Watterson channel simulator
! - Add noise to the imaginary part of cdat and write to wav file.
use wavhdr
use qpc_mod
use sfox_mod
type(hdr) h !Header for .wav file
logical*1 bMoreCQs !Include a CQ when space available?
logical*1 bSendMsg !Send a Free text message
integer*2 iwave(NMAX) !Generated i*2 waveform
integer isync(24) !Indices of sync symbols
integer itone(151) !Symbol values, data and sync
integer*1 xin(0:49)
integer*1 y(0:127)
real*4 xnoise(NMAX) !Random noise
real*4 dat(NMAX) !Generated real data
complex cdat(NMAX) !Generated complex waveform
complex crcvd(NMAX) !Signal as received
real, allocatable :: s3(:,:) !Symbol spectra: will be s3(NQ,NN)
integer, allocatable :: msg0(:) !Information symbols
integer, allocatable :: chansym(:) !Encoded data, 7-bit integers
character fname*17,arg*12,channel*2,foxcall*11
character*10 ckey
character*26 text_msg
character*120 line !SuperFox message pieces
character*40 cmsg(5)
data ckey/'0000000000'/
data cmsg/'W0AAA RR73; W5FFF <K1JT> -18', &
'W1BBB RR73; W6GGG <K1JT> -15', &
'W2CCC RR73; W7HHH <K1JT> -12', &
'W3DDD RR73; W8III <K1JT> -09', &
'W4EEE RR73; W9JJJ <K1JT> -06'/
data text_msg/'0123456789ABCDEFGHIJKLMNOP'/
data isync/1,2,4,7,11,16,22,29,37,39,42,43,45,48,52,57,63,70,78,80, &
83,84,86,89/
nargs=iargc()
if(nargs.ne.11) then
print*,'Usage: sfoxsim f0 DT Chan FoxC H1 H2 CQ FT nfiles snr'
print*,'Example: sfoxsim 750 0.0 MM K1JT 5 1 0 0 10 -15'
print*,' f0=0 to dither f0 and DT'
print*,' Chan Channel type AW LQ LM LD MQ MM MD HQ HM HD'
print*,' FoxC Fox callsign'
print*,' key'
print*,' H1 number of Hound calls with RR73'
print*,' H2 number of Hound calls with reports'
print*,' CQ=1 to include a CQ message'
print*,' FT=1 to include a Free Text message'
go to 999
endif
call getarg(1,arg)
read(arg,*) f0
call getarg(2,arg)
read(arg,*) xdt
call getarg(3,channel)
call getarg(4,foxcall)
call getarg(6,arg)
read(arg,*) nh1
call getarg(7,arg)
read(arg,*) nh2
call getarg(8,arg)
read(arg,*) ncq
bMoreCQs=ncq.ne.0
call getarg(9,arg)
read(arg,*) nft
bSendMsg=nft.ne.0
call getarg(10,arg)
read(arg,*) nfiles
call getarg(11,arg)
read(arg,*) snr
fspread=0.0
delay=0.0
fsample=12000.0 !Sample rate (Hz)
call sfox_init(7,127,50,channel,fspread,delay,fsample,24)
txt=(NN+NS)*NSPS/fsample
write(*,1000) f0,xdt,channel,snr
1000 format('sfoxsim: f0= ',f5.1,' dt= ',f4.2,' Channel: ',a2,' snr: ',f5.1,' dB')
! Allocate storage for arrays that depend on code parameters.
allocate(s3(0:NQ-1,0:NN-1))
allocate(msg0(1:KK))
allocate(chansym(0:NN-1))
if(nft.ne.0) then
open(10,file='text_msg.txt',status='old',err=2)
read(10,*) text_msg
endif
2 idum=-1
rms=100.
baud=fsample/nsps !Keying rate, 11.719 baud for nsps=1024
bandwidth_ratio=2500.0/fsample
do i=1,5
cmsg(i)=cmsg(i)(1:19)//trim(foxcall)//cmsg(i)(24:28)
if(i.gt.nh1 .and. i.gt.nh2) then
cmsg(i)=''
elseif(i.gt.nh1) then
cmsg(i)=cmsg(i)(13:18)//trim(foxcall)//cmsg(i)(25:28)
elseif(i.gt.nh2) then
cmsg(i)=cmsg(i)(1:6)//trim(foxcall)//' RR73'
endif
! write(*,*) 'Debug ',cmsg(i)
enddo
! Generate a SuperFox message
nslots=5
call foxgen2(nslots,cmsg,line,foxcall) !Parse old-style Fox messages
call sfox_pack(line,ckey,bMoreCQs,bSendMsg,text_msg,xin)
call qpc_encode(y,xin)
y=cshift(y,1)
y(127)=0
chansym=y(0:126)
sig=sqrt(2*bandwidth_ratio)*10.0**(0.05*snr)
sigr=sqrt(2.)*sig
if(snr.gt.90.0) sig=1.0
do ifile=1,nfiles
xnoise=0.
if(snr.lt.90) then
do i=1,NMAX
xnoise(i)=gran() !Gaussian noise
enddo
endif
f1=f0
if(f0.eq.0.0) then
f1=750 + 20.0*(ran1(idum)-0.5)
xdt=ran1(idum)-0.5
endif
! Generate cdat, the SuperFox waveform
call sfox_gen_gfsk(chansym,f1,isync,itone,cdat)
crcvd=0.
crcvd(1:NMAX)=cshift(cdat(1:NMAX),-nint((0.5+xdt)*fsample))
if(fspread.ne.0 .or. delay.ne.0) call watterson(crcvd,NMAX,NZ,fsample,&
delay,fspread)
dat=aimag(sigr*crcvd(1:NMAX)) + xnoise !Add generated AWGN noise
fac=32767.0
if(snr.ge.90.0) iwave(1:NMAX)=nint(fac*dat(1:NMAX))
if(snr.lt.90.0) iwave(1:NMAX)=nint(rms*dat(1:NMAX))
h=default_header(12000,NMAX)
fname='000000_000001.wav'
nsec=(ifile-1)*30
nhr=nsec/3600
nmin=(nsec-nhr*3600)/60
nsec=mod(nsec,60)
write(fname(8:13),'(3i2.2)') nhr,nmin,nsec
open(10,file=trim(fname),access='stream',status='unknown')
write(10) h,iwave(1:NMAX) !Save the .wav file
close(10)
enddo ! ifile
999 end program sfoxsim