2024-02-01 10:51:48 -05:00
|
|
|
program sfoxtest
|
2024-01-30 18:10:44 -05:00
|
|
|
|
2024-02-08 13:06:54 -05:00
|
|
|
! Generate and test possible waveforms for SuperFox signal.
|
2024-01-30 18:10:44 -05:00
|
|
|
|
|
|
|
use wavhdr
|
2024-02-08 10:45:43 -05:00
|
|
|
use sfox_mod
|
2024-02-16 10:51:27 -05:00
|
|
|
use timer_module, only: timer
|
|
|
|
use timer_impl, only: init_timer !, limtrace
|
|
|
|
|
2024-01-30 18:10:44 -05:00
|
|
|
type(hdr) h !Header for .wav file
|
|
|
|
integer*2 iwave(NMAX) !Generated i*2 waveform
|
2024-02-15 15:46:09 -05:00
|
|
|
integer param(0:8)
|
2024-01-30 18:10:44 -05:00
|
|
|
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 cnoise(NMAX) !Complex noise
|
2024-01-30 18:34:43 -05:00
|
|
|
complex crcvd(NMAX) !Signal as received
|
2024-02-08 12:21:36 -05:00
|
|
|
real a(3)
|
2024-02-15 08:53:44 -05:00
|
|
|
real, allocatable :: s3(:,:) !Symbol spectra: will be s3(NQ,NN)
|
2024-02-08 10:45:43 -05:00
|
|
|
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
|
2024-02-13 14:56:20 -05:00
|
|
|
integer, allocatable :: rxdat(:)
|
|
|
|
integer, allocatable :: rxprob(:)
|
|
|
|
integer, allocatable :: rxdat2(:)
|
|
|
|
integer, allocatable :: rxprob2(:)
|
2024-02-15 08:53:44 -05:00
|
|
|
integer, allocatable :: correct(:)
|
2024-02-20 09:07:02 -05:00
|
|
|
logical hard_sync
|
2024-02-08 13:46:11 -05:00
|
|
|
character fname*17,arg*12,itu*2
|
2024-02-08 12:21:36 -05:00
|
|
|
|
2024-01-30 18:10:44 -05:00
|
|
|
nargs=iargc()
|
2024-02-22 14:35:41 -05:00
|
|
|
if(nargs.ne.11) then
|
|
|
|
print*,'Usage: sfoxtest f0 DT ITU M N K ts v hs nfiles snr'
|
|
|
|
print*,'Example: sfoxtest 1500 0.15 MM 7 127 48 3 0 F 10 -10'
|
2024-02-10 19:54:25 -05:00
|
|
|
print*,' f0=0 means f0, DT will assume suitable random values'
|
2024-02-10 15:09:37 -05:00
|
|
|
print*,' LQ: Low Latitude Quiet'
|
|
|
|
print*,' MM: Mid Latitude Moderate'
|
|
|
|
print*,' HD: High Latitude Disturbed'
|
2024-02-10 19:54:25 -05:00
|
|
|
print*,' ... and similarly for LM LD MQ MD HQ HM'
|
2024-02-22 14:35:41 -05:00
|
|
|
print*,' ts: approximate sync duration (s)'
|
2024-02-10 15:09:37 -05:00
|
|
|
print*,' v=1 for .wav files, 2 for verbose output, 3 for both'
|
2024-02-20 09:07:02 -05:00
|
|
|
print*,' hs = T for hard-wired sync'
|
2024-02-22 13:41:09 -05:00
|
|
|
print*,' snr=0 means loop over SNRs'
|
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
|
2024-02-08 13:46:11 -05:00
|
|
|
call getarg(3,itu)
|
2024-01-30 18:10:44 -05:00
|
|
|
call getarg(4,arg)
|
2024-02-08 12:21:36 -05:00
|
|
|
read(arg,*) mm0
|
2024-02-08 13:46:11 -05:00
|
|
|
call getarg(5,arg)
|
2024-02-08 12:21:36 -05:00
|
|
|
read(arg,*) nn0
|
2024-02-08 13:46:11 -05:00
|
|
|
call getarg(6,arg)
|
2024-02-08 12:21:36 -05:00
|
|
|
read(arg,*) kk0
|
2024-02-08 13:46:11 -05:00
|
|
|
call getarg(7,arg)
|
2024-02-22 14:35:41 -05:00
|
|
|
read(arg,*) ts
|
2024-02-22 13:41:09 -05:00
|
|
|
call getarg(8,arg)
|
2024-02-22 14:35:41 -05:00
|
|
|
read(arg,*) nv
|
2024-02-22 13:41:09 -05:00
|
|
|
call getarg(9,arg)
|
2024-02-22 14:35:41 -05:00
|
|
|
hard_sync=arg(1:1).eq.'T'
|
2024-02-22 13:41:09 -05:00
|
|
|
call getarg(10,arg)
|
2024-02-22 14:35:41 -05:00
|
|
|
read(arg,*) nfiles
|
|
|
|
call getarg(11,arg)
|
2024-01-30 18:10:44 -05:00
|
|
|
read(arg,*) snrdb
|
|
|
|
|
2024-02-16 10:51:27 -05:00
|
|
|
call init_timer ('timer.out')
|
|
|
|
call timer('sfoxtest',0)
|
|
|
|
|
2024-02-21 13:33:37 -05:00
|
|
|
fsample=12000.0 !Sample rate (Hz)
|
2024-02-22 14:35:41 -05:00
|
|
|
call sfox_init(mm0,nn0,kk0,itu,fspread,delay,fsample,ts)
|
2024-02-21 13:33:37 -05:00
|
|
|
baud=fsample/NSPS
|
2024-02-10 09:47:11 -05:00
|
|
|
tsym=1.0/baud
|
2024-02-08 10:45:43 -05:00
|
|
|
bw=NQ*baud
|
2024-02-08 13:58:00 -05:00
|
|
|
maxerr=(NN-KK)/2
|
2024-02-21 13:33:37 -05:00
|
|
|
tsync=NSYNC/fsample
|
|
|
|
txt=(NN+NS)*NSPS/fsample
|
2024-02-09 13:36:01 -05:00
|
|
|
|
|
|
|
write(*,1000) MM,NN,KK,NSPS,baud,bw,itu,fspread,delay,maxerr, &
|
|
|
|
tsync,txt
|
2024-02-08 10:45:43 -05:00
|
|
|
1000 format('M:',i2,' Base code: (',i3,',',i3,') NSPS:',i5, &
|
2024-02-08 13:46:11 -05:00
|
|
|
' Symbol Rate:',f7.3,' BW:',f6.0/ &
|
2024-02-09 13:36:01 -05:00
|
|
|
'Channel: ',a2,' fspread:',f4.1,' delay:',f5.1, &
|
|
|
|
' MaxErr:',i3,' tsync:',f4.1,' TxT:',f5.1/)
|
2024-02-08 13:06:54 -05:00
|
|
|
|
|
|
|
! Allocate storage for arrays that depend on code parameters.
|
2024-02-15 08:53:44 -05:00
|
|
|
allocate(s3(0:NQ-1,0:NN-1))
|
2024-02-08 10:45:43 -05:00
|
|
|
allocate(msg0(1:KK))
|
|
|
|
allocate(parsym(1:NN-KK))
|
2024-02-15 15:46:09 -05:00
|
|
|
allocate(chansym0(0:NN-1))
|
|
|
|
allocate(chansym(0:NN-1))
|
|
|
|
allocate(iera(0:NN-1))
|
2024-02-15 08:53:44 -05:00
|
|
|
allocate(rxdat(0:NN-1))
|
|
|
|
allocate(rxprob(0:NN-1))
|
|
|
|
allocate(rxdat2(0:NN-1))
|
|
|
|
allocate(rxprob2(0:NN-1))
|
|
|
|
allocate(correct(0:NN-1))
|
2024-02-08 10:45:43 -05:00
|
|
|
|
2024-01-30 18:10:44 -05:00
|
|
|
rms=100.
|
2024-02-21 13:33:37 -05:00
|
|
|
baud=fsample/nsps !Keying rate, 11.719 baud for nsps=1024
|
2024-01-31 15:13:42 -05:00
|
|
|
idummy=0
|
2024-02-21 13:33:37 -05:00
|
|
|
bandwidth_ratio=2500.0/fsample
|
2024-02-10 13:35:06 -05:00
|
|
|
fgood0=1.0
|
2024-01-31 15:13:42 -05:00
|
|
|
|
2024-02-02 15:44:03 -05:00
|
|
|
! Generate a message
|
2024-02-07 14:24:05 -05:00
|
|
|
msg0=0
|
2024-02-14 11:49:59 -05:00
|
|
|
do i=1,KK
|
2024-02-10 13:35:06 -05:00
|
|
|
msg0(i)=int(NQ*ran1(idummy))
|
2024-01-31 19:21:02 -05:00
|
|
|
enddo
|
2024-02-02 15:44:03 -05:00
|
|
|
|
|
|
|
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
|
2024-02-15 15:46:09 -05:00
|
|
|
chansym0(0:kk-1)=msg0(1:kk)
|
|
|
|
chansym0(kk:nn-1)=parsym(1:nn-kk)
|
2024-02-16 16:11:01 -05:00
|
|
|
! chansym0=NQ/2 !### TEMPORARY, for SNR calibration ###
|
2024-02-07 14:24:05 -05:00
|
|
|
|
2024-02-10 13:35:06 -05:00
|
|
|
! Generate cdat, the SuperFox waveform
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('gen ',0)
|
2024-02-22 13:41:09 -05:00
|
|
|
call sfox_gen(chansym0,f0,fsample,cdat)
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('gen ',1)
|
2024-02-15 13:36:48 -05:00
|
|
|
isnr0=-8
|
2024-01-31 19:21:02 -05:00
|
|
|
|
2024-02-15 13:36:48 -05:00
|
|
|
do isnr=isnr0,-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)
|
2024-02-17 11:00:33 -05:00
|
|
|
sigr=sqrt(2.)*sig
|
2024-01-31 18:59:41 -05:00
|
|
|
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-02-09 13:36:01 -05:00
|
|
|
sqt=0.
|
|
|
|
sqf=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
|
2024-02-22 13:41:09 -05:00
|
|
|
f1=1500.0 + 20.0*(ran1(idummy)-0.5)
|
2024-02-15 08:53:44 -05:00
|
|
|
xdt=0.3*ran1(idummy)
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('gen ',0)
|
2024-02-22 13:41:09 -05:00
|
|
|
call sfox_gen(chansym0,f1,fsample,cdat)
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('gen ',1)
|
2024-01-31 19:35:08 -05:00
|
|
|
endif
|
|
|
|
|
2024-01-31 18:59:41 -05:00
|
|
|
crcvd=0.
|
2024-02-21 14:21:05 -05:00
|
|
|
crcvd(1:NMAX)=cshift(cdat(1:NMAX),-nint(xdt*fsample))
|
2024-02-16 16:11:01 -05:00
|
|
|
call timer('watterso',0)
|
|
|
|
if(fspread.ne.0 .or. delay.ne.0) call watterson(crcvd,NMAX,NZ,fsample,&
|
|
|
|
delay,fspread)
|
|
|
|
call timer('watterso',1)
|
2024-02-21 14:21:05 -05:00
|
|
|
crcvd=sig*crcvd+cnoise
|
2024-01-30 18:10:44 -05:00
|
|
|
|
2024-02-17 11:00:33 -05:00
|
|
|
dat=aimag(sigr*cdat(1:NMAX)) + xnoise !Add generated AWGN noise
|
2024-01-31 18:59:41 -05:00
|
|
|
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-02-20 09:07:02 -05:00
|
|
|
if(hard_sync) then
|
2024-02-22 13:41:09 -05:00
|
|
|
f=f1 ! + 5.0*(ran1(idummy)-0.5)
|
|
|
|
t=xdt ! + 0.01*(ran1(idummy)-0.5)
|
2024-02-20 09:07:02 -05:00
|
|
|
else
|
2024-01-31 12:46:24 -05:00
|
|
|
! Find signal freq and DT
|
2024-02-20 09:07:02 -05:00
|
|
|
call timer('sync ',0)
|
2024-02-22 14:25:17 -05:00
|
|
|
call sfox_sync(crcvd,fsample,f,t)
|
2024-02-20 09:07:02 -05:00
|
|
|
call timer('sync ',1)
|
|
|
|
endif
|
2024-01-31 19:35:08 -05:00
|
|
|
ferr=f-f1
|
2024-01-31 18:59:41 -05:00
|
|
|
terr=t-xdt
|
2024-02-15 08:53:44 -05:00
|
|
|
igoodsync=0
|
2024-02-21 14:57:44 -05:00
|
|
|
if(abs(ferr).lt.baud/2.0 .and. abs(terr).lt.tsym/4.0) then
|
2024-02-15 08:53:44 -05:00
|
|
|
igoodsync=1
|
2024-02-09 13:36:01 -05:00
|
|
|
ngoodsync=ngoodsync+1
|
|
|
|
sqt=sqt + terr*terr
|
|
|
|
sqf=sqf + ferr*ferr
|
2024-02-20 09:07:02 -05:00
|
|
|
endif
|
2024-01-31 12:46:24 -05:00
|
|
|
|
2024-02-22 13:41:09 -05:00
|
|
|
write(50,3050) ifile,ferr/baud,terr/tsym
|
|
|
|
3050 format(i8,2f10.4)
|
|
|
|
flush(50)
|
|
|
|
! write(51) snr,f1,xdt,crcvd(1:76000)
|
|
|
|
|
2024-02-08 12:21:36 -05:00
|
|
|
a=0.
|
|
|
|
a(1)=1500.0-f
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('twkfreq ',0)
|
2024-02-21 13:33:37 -05:00
|
|
|
call twkfreq(crcvd,crcvd,NMAX,fsample,a)
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('twkfreq ',1)
|
2024-02-08 12:21:36 -05:00
|
|
|
f=1500.0
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('demod ',0)
|
2024-02-13 12:02:04 -05:00
|
|
|
call sfox_demod(crcvd,f,t,s3,chansym) !Get s3 and hard symbol values
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('demod ',1)
|
|
|
|
|
|
|
|
call timer('prob ',0)
|
2024-02-13 14:56:20 -05:00
|
|
|
call sym_prob(s3,rxdat,rxprob,rxdat2,rxprob2)
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('prob ',1)
|
2024-02-10 13:35:06 -05:00
|
|
|
|
2024-02-02 15:44:03 -05:00
|
|
|
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-04 22:01:53 -05:00
|
|
|
ntot=ntot+nharderr
|
2024-02-05 16:25:51 -05:00
|
|
|
nworst=max(nworst,nharderr)
|
2024-02-15 15:46:09 -05:00
|
|
|
|
2024-02-21 09:23:45 -05:00
|
|
|
ntrials=1000
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('ftrsd3 ',0)
|
2024-02-15 15:46:09 -05:00
|
|
|
call ftrsd3(s3,chansym0,rxdat,rxprob,rxdat2,rxprob2,ntrials, &
|
|
|
|
correct,param,ntry)
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('ftrsd3 ',1)
|
2024-02-15 15:46:09 -05:00
|
|
|
|
2024-02-10 13:56:45 -05:00
|
|
|
if(iand(nv,1).ne.0) then
|
2024-02-21 13:33:37 -05:00
|
|
|
h=default_header(12000,NMAX)
|
2024-01-31 18:59:41 -05:00
|
|
|
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-02-15 15:46:09 -05:00
|
|
|
endif
|
2024-02-02 21:08:45 -05:00
|
|
|
|
2024-02-15 15:46:09 -05:00
|
|
|
if(count(correct.ne.chansym0).eq.0) ngood=ngood+1
|
2024-01-31 18:59:41 -05:00
|
|
|
enddo ! ifile
|
|
|
|
fgoodsync=float(ngoodsync)/nfiles
|
|
|
|
fgood=float(ngood)/nfiles
|
2024-02-15 13:36:48 -05:00
|
|
|
if(isnr.eq.isnr0) write(*,1300)
|
2024-02-22 14:35:41 -05:00
|
|
|
1300 format(' SNR Eb/No iters fsync fgood averr worst rmsf rmst'/ &
|
2024-02-20 08:46:48 -05:00
|
|
|
'------------------------------------------------------------')
|
2024-02-10 09:47:11 -05:00
|
|
|
ave_harderr=float(ntot)/nfiles
|
|
|
|
rmst=sqrt(sqt/ngoodsync)
|
|
|
|
rmsf=sqrt(sqf/ngoodsync)
|
2024-02-20 08:46:48 -05:00
|
|
|
ebno=snr-10*log10(baud/2500*mm0*KK/NN)
|
|
|
|
write(*,1310) snr,ebno,nfiles,fgoodsync,fgood,ave_harderr,nworst,rmsf,rmst
|
2024-02-22 14:35:41 -05:00
|
|
|
1310 format(f7.2,f7.2 i6,2f7.4,f7.1,i6,f6.1,f7.3)
|
2024-02-10 09:47:11 -05:00
|
|
|
if(fgood.le.0.5 .and. fgood0.gt.0.5) then
|
|
|
|
threshold=isnr + 1 - (fgood0-0.50)/(fgood0-fgood+0.000001)
|
2024-02-08 13:06:54 -05:00
|
|
|
endif
|
2024-02-10 09:47:11 -05:00
|
|
|
fgood0=fgood
|
2024-01-31 18:59:41 -05:00
|
|
|
if(snrdb.ne.0.0) exit
|
2024-02-22 13:41:09 -05:00
|
|
|
! if(fgood.eq.0.0) exit
|
2024-01-31 18:59:41 -05:00
|
|
|
if(fgoodsync.lt.0.5) exit
|
|
|
|
enddo ! isnr
|
2024-02-10 10:50:42 -05:00
|
|
|
if(snrdb.eq.0.0) write(*,1320) threshold
|
|
|
|
1320 format(/'Threshold sensitivity (50% decoding):',f6.1,' dB')
|
2024-02-16 10:51:27 -05:00
|
|
|
call timer('sfoxtest',1)
|
2024-01-30 18:10:44 -05:00
|
|
|
|
2024-02-16 10:51:27 -05:00
|
|
|
999 call timer('sfoxtest',101)
|
|
|
|
end program sfoxtest
|
2024-02-16 16:11:01 -05:00
|
|
|
|