WSJT-X/lib/superfox/sfoxtest.f90

173 lines
5.4 KiB
Fortran
Raw Normal View History

program sfoxtest
! Generate and test sync waveforms for possible use in SuperFox signal.
use wavhdr
use sfox_mod
! include "sfox_params.f90"
type(hdr) h !Header for .wav file
integer*2 iwave(NMAX) !Generated i*2 waveform
real*4 xnoise(NMAX) !Random noise
real*4 dat(NMAX) !Generated real data
complex cdat(NMAX) !Generated complex waveform
complex clo(NMAX) !Complex Local Oscillator
complex cnoise(NMAX) !Complex noise
complex crcvd(NMAX) !Signal as received
integer, allocatable :: msg0(:) !Information symbols
integer, allocatable :: parsym(:) !Parity symbols
integer, allocatable :: chansym0(:) !Encoded data, 7-bit integers
integer, allocatable :: chansym(:) !Recovered hard-decision symbols
integer, allocatable :: iera(:) !Positions of erasures
character fname*17,arg*12
nargs=iargc()
if(nargs.ne.8) then
2024-02-02 21:08:45 -05:00
print*,'Usage: sfoxtest f0 DT fspread delay width nran nfiles snr'
print*,'Example: sfoxtest 1500.0 0.15 0.5 1.0 100 0 10 -10'
go to 999
endif
call getarg(1,arg)
read(arg,*) f0
call getarg(2,arg)
read(arg,*) xdt
call getarg(3,arg)
read(arg,*) fspread
call getarg(4,arg)
read(arg,*) delay
call getarg(5,arg)
read(arg,*) syncwidth
call getarg(6,arg)
read(arg,*) nran
call getarg(7,arg)
read(arg,*) nfiles
call getarg(8,arg)
read(arg,*) snrdb
call sfox_init
baud=12000.0/NSPS
bw=NQ*baud
write(*,1000) MM,NN,KK,NSPS,baud,bw
1000 format('M:',i2,' Base code: (',i3,',',i3,') NSPS:',i5, &
' Symbol Rate:',f7.3,' BW:',f6.0)
allocate(msg0(1:KK))
allocate(parsym(1:NN-KK))
allocate(chansym0(1:NN))
allocate(chansym(1:NN))
allocate(iera(1:NN))
rms=100.
fsample=12000.0 !Sample rate (Hz)
2024-01-31 10:47:16 -05:00
baud=12000.0/nsps !Keying rate, 11.719 baud for nsps=1024
h=default_header(12000,NMAX)
idummy=0
bandwidth_ratio=2500.0/6000.0
! Generate a message
2024-02-07 14:24:05 -05:00
msg0=0
do i=1,KK-2
2024-02-07 14:24:05 -05:00
msg0(i)=i
2024-01-31 19:21:02 -05:00
enddo
2024-02-07 14:24:05 -05:00
! Append a CRC here ...
call rs_init_sf(MM,NQ,NN,KK,NFZ) !Initialize the Karn codec
2024-02-07 14:24:05 -05:00
call rs_encode_sf(msg0,parsym) !Compute parity symbols
chansym0(1:kk)=msg0(1:kk)
chansym0(kk+1:nn)=parsym(1:nn-kk)
2024-01-31 19:21:02 -05:00
! Generate cdat (SuperFox waveform) and clo (LO for sync detection)
2024-02-07 14:24:05 -05:00
call gen_sfox(chansym0,f0,fsample,syncwidth,cdat,clo)
2024-01-31 19:21:02 -05:00
do isnr=0,-20,-1
2024-01-31 18:59:41 -05:00
snr=isnr
if(snrdb.ne.0.0) snr=snrdb
sig=sqrt(2*bandwidth_ratio)*10.0**(0.05*snr)
if(snr.gt.90.0) sig=1.0
ngoodsync=0
ngood=0
2024-02-04 22:01:53 -05:00
ntot=0
2024-02-05 16:25:51 -05:00
nworst=0
2024-01-31 18:59:41 -05:00
do ifile=1,nfiles
xnoise=0.
cnoise=0.
if(snr.lt.90) then
do i=1,NMAX !Generate Gaussian noise
x=gran()
y=gran()
xnoise(i)=x
cnoise(i)=cmplx(x,y)
enddo
endif
2024-01-31 19:35:08 -05:00
f1=f0
if(f0.eq.0.0) then
f1=1500.0 + 200.0*(ran1(idummy)-0.5)
xdt=2.0*(ran1(idummy)-0.5)
2024-02-07 14:24:05 -05:00
call gen_sfox(chansym0,f1,fsample,syncwidth,cdat,clo)
2024-01-31 19:35:08 -05:00
endif
2024-01-31 18:59:41 -05:00
crcvd=0.
crcvd(1:NMAX)=cshift(sig*cdat(1:NMAX),-nint(xdt*fsample)) + cnoise
2024-01-31 18:59:41 -05:00
dat=aimag(sig*cdat(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))
2024-01-31 18:59:41 -05:00
if(fspread.ne.0 .or. delay.ne.0) call watterson(crcvd,NMAX,NZ,fsample,&
delay,fspread)
2024-01-31 12:46:24 -05:00
! Find signal freq and DT
2024-01-31 18:59:41 -05:00
call sync_sf(crcvd,clo,snrdb,f,t)
2024-01-31 19:35:08 -05:00
ferr=f-f1
2024-01-31 18:59:41 -05:00
terr=t-xdt
2024-02-08 04:11:12 -05:00
if(abs(ferr).lt.3.0 .and. abs(terr).lt.0.01) ngoodsync=ngoodsync+1
2024-01-31 12:46:24 -05:00
2024-02-07 14:24:05 -05:00
call hard_symbols(crcvd,f,t,chansym) !Get hard symbol values
nera=0
2024-02-07 14:24:05 -05:00
chansym=mod(chansym,nq) !Enforce 0 to nq-1
nharderr=count(chansym.ne.chansym0) !Count hard errors
2024-02-08 04:11:12 -05:00
! write(71,3071) f1,f,ferr,xdt,t,terr,nharderr
!3071 format(6f10.3,i6)
2024-02-04 22:01:53 -05:00
ntot=ntot+nharderr
2024-02-05 16:25:51 -05:00
nworst=max(nworst,nharderr)
2024-02-07 14:24:05 -05:00
call rs_decode_sf(chansym,iera,nera,nfixed) !Call the decoder
2024-01-31 18:59:41 -05:00
if(snrdb.ne.0) then
fname='000000_000001.wav'
write(fname(8:13),'(i6.6)') ifile
open(10,file=trim(fname),access='stream',status='unknown')
write(10) h,iwave(1:NMAX) !Save the .wav file
close(10)
2024-01-31 19:35:08 -05:00
write(*,1100) f1,xdt
2024-01-31 18:59:41 -05:00
1100 format(/'f0:',f7.1,' xdt:',f6.2)
write(*,1112) f,t
1112 format('f: ',f7.1,' DT:',f6.2)
write(*,1110) ferr,terr
1110 format('err:',f6.1,f12.2)
write(*,1120) nharderr
1120 format('Hard errors:',i4)
endif
2024-02-02 21:08:45 -05:00
2024-01-31 19:39:45 -05:00
if(nharderr.le.38) ngood=ngood+1 !(125-49)/2 = 38
! write(13,1200) ifile,snr,ferr,terr,nharderr
!1200 format(i5,3f10.3,i5)
2024-01-31 18:59:41 -05:00
enddo ! ifile
2024-02-07 14:24:05 -05:00
! print*,'D'
2024-01-31 18:59:41 -05:00
fgoodsync=float(ngoodsync)/nfiles
fgood=float(ngood)/nfiles
if(isnr.eq.0) write(*,1300)
1300 format(' SNR N fsync fgood averr worst'/ &
2024-02-05 16:25:51 -05:00
'-----------------------------------------')
2024-02-04 22:01:53 -05:00
ave_harderr=float(ntot)/nfiles
2024-02-05 16:25:51 -05:00
write(*,1310) snr,nfiles,fgoodsync,fgood,ave_harderr,nworst
1310 format(f7.2,i6,2f7.2,f7.1,i6)
2024-01-31 18:59:41 -05:00
if(snrdb.ne.0.0) exit
if(fgoodsync.lt.0.5) exit
enddo ! isnr
999 end program sfoxtest