2024-02-01 10:51:48 -05:00
|
|
|
program sfoxtest
|
2024-01-30 18:10:44 -05:00
|
|
|
|
|
|
|
! Generate and test sync waveforms for possible use in SuperFox signal.
|
|
|
|
|
|
|
|
use wavhdr
|
2024-01-31 11:18:42 -05:00
|
|
|
include "sfox_params.f90"
|
2024-01-30 18:10:44 -05:00
|
|
|
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
|
2024-01-30 18:34:43 -05:00
|
|
|
complex cdat(NMAX) !Generated complex waveform
|
2024-01-30 18:10:44 -05:00
|
|
|
complex clo(NMAX) !Complex Local Oscillator
|
|
|
|
complex cnoise(NMAX) !Complex noise
|
2024-01-30 18:34:43 -05:00
|
|
|
complex crcvd(NMAX) !Signal as received
|
2024-02-02 15:44:03 -05:00
|
|
|
integer imsg(KK) !Information symbols
|
|
|
|
integer jmsg(KK) !Decoded information
|
|
|
|
integer*1 imsg1(7*KK) !Copy of imsg in 1-bit i*1 format
|
|
|
|
integer idat(NN) !Encoded data, 7-bit integers
|
|
|
|
integer jdat(NN) !Recovered hard-decision symbols
|
2024-01-30 18:10:44 -05:00
|
|
|
character fname*17,arg*12
|
2024-02-02 15:44:03 -05:00
|
|
|
character c357*357,c14*14 !,chkmsg*15
|
2024-01-30 18:10:44 -05:00
|
|
|
|
|
|
|
nargs=iargc()
|
2024-01-31 15:13:42 -05:00
|
|
|
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'
|
2024-01-30 18:10:44 -05:00
|
|
|
go to 999
|
|
|
|
endif
|
|
|
|
call getarg(1,arg)
|
|
|
|
read(arg,*) f0
|
|
|
|
call getarg(2,arg)
|
|
|
|
read(arg,*) xdt
|
|
|
|
call getarg(3,arg)
|
2024-01-31 11:37:19 -05:00
|
|
|
read(arg,*) fspread
|
2024-01-30 18:10:44 -05:00
|
|
|
call getarg(4,arg)
|
2024-01-31 11:37:19 -05:00
|
|
|
read(arg,*) delay
|
|
|
|
call getarg(5,arg)
|
|
|
|
read(arg,*) syncwidth
|
|
|
|
call getarg(6,arg)
|
2024-01-31 15:13:42 -05:00
|
|
|
read(arg,*) nran
|
|
|
|
call getarg(7,arg)
|
|
|
|
read(arg,*) nfiles
|
|
|
|
call getarg(8,arg)
|
2024-01-30 18:10:44 -05:00
|
|
|
read(arg,*) snrdb
|
|
|
|
|
|
|
|
rms=100.
|
2024-01-30 18:34:43 -05:00
|
|
|
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
|
2024-01-31 11:18:42 -05:00
|
|
|
h=default_header(12000,NMAX)
|
2024-01-31 15:13:42 -05:00
|
|
|
idummy=0
|
2024-01-30 18:10:44 -05:00
|
|
|
bandwidth_ratio=2500.0/6000.0
|
2024-01-31 15:13:42 -05:00
|
|
|
|
2024-02-02 15:44:03 -05:00
|
|
|
! Generate a message
|
|
|
|
do i=1,KK-2
|
|
|
|
imsg(i)=i
|
2024-01-31 19:21:02 -05:00
|
|
|
enddo
|
2024-02-02 15:44:03 -05:00
|
|
|
|
|
|
|
! Append a 14-bit CRC
|
|
|
|
imsg(KK-1:KK)=0
|
|
|
|
write(c357,'(51b7.7)') imsg(1:KK)
|
|
|
|
read(c357,'(357i1)') imsg1
|
|
|
|
call get_crc14(imsg1,7*KK,ncrc0)
|
|
|
|
write(c14,'(b14.14)') ncrc0
|
|
|
|
read(c14,'(2b7.7)') imsg(KK-1:KK)
|
|
|
|
|
|
|
|
call rs_init_sf(MM,NQ,NN,KK,NFZ) !Initialize the Karn codec
|
|
|
|
call rs_encode_sf(imsg,idat) !Encode imsg into idat
|
2024-01-31 19:21:02 -05:00
|
|
|
|
|
|
|
! Generate cdat (SuperFox waveform) and clo (LO for sync detection)
|
|
|
|
call gen_sfox(idat,f0,fsample,syncwidth,cdat,clo)
|
|
|
|
|
2024-01-31 18:59:41 -05:00
|
|
|
do isnr=0,-30,-1
|
|
|
|
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-01-31 15:13:42 -05:00
|
|
|
|
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-30 18:10:44 -05:00
|
|
|
|
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)
|
|
|
|
call gen_sfox(idat,f1,fsample,syncwidth,cdat,clo)
|
|
|
|
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-30 18:10:44 -05:00
|
|
|
|
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-30 18:10:44 -05:00
|
|
|
|
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 11:37:19 -05:00
|
|
|
|
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-01-31 21:07:58 -05:00
|
|
|
if(abs(ferr).lt.5.0 .and. abs(terr).lt.0.01) ngoodsync=ngoodsync+1
|
2024-01-31 12:46:24 -05:00
|
|
|
|
2024-01-31 19:39:45 -05:00
|
|
|
call hard_symbols(crcvd,f,t,jdat) !Get hard symbol values
|
2024-02-02 15:44:03 -05:00
|
|
|
nera=0
|
|
|
|
call rs_decode_sf(idat,iera,nera,jmsg,nfixed) !Call the decoder
|
|
|
|
write(c357,'(51b7.7)') jmsg(1:KK)
|
|
|
|
read(c357,'(357i1)') imsg11
|
|
|
|
call get_crc14(imsg1,7*KK,ncrc)
|
|
|
|
|
2024-01-31 19:39:45 -05:00
|
|
|
nharderr=count(jdat.ne.idat) !Count hard errors
|
2024-02-04 22:01:53 -05:00
|
|
|
ntot=ntot+nharderr
|
2024-01-31 13:45:53 -05:00
|
|
|
|
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
|
|
|
|
fgoodsync=float(ngoodsync)/nfiles
|
|
|
|
fgood=float(ngood)/nfiles
|
|
|
|
if(isnr.eq.0) write(*,1300)
|
|
|
|
1300 format(' SNR N fsync fgood'/ &
|
|
|
|
'----------------------------')
|
2024-02-04 22:01:53 -05:00
|
|
|
ave_harderr=float(ntot)/nfiles
|
|
|
|
write(*,1310) snr,nfiles,fgoodsync,fgood,ave_harderr
|
|
|
|
1310 format(f7.2,i6,2f7.2,f7.1)
|
2024-01-31 18:59:41 -05:00
|
|
|
if(snrdb.ne.0.0) exit
|
|
|
|
if(fgoodsync.lt.0.5) exit
|
|
|
|
enddo ! isnr
|
2024-01-30 18:10:44 -05:00
|
|
|
|
2024-02-01 10:51:48 -05:00
|
|
|
999 end program sfoxtest
|