Good working model with random sync symbols rather than sweeping sync.

This commit is contained in:
Joe Taylor 2024-02-23 10:44:49 -05:00
parent 12bcddf366
commit 1b9071fd8c
5 changed files with 39 additions and 19 deletions

View File

@ -74,6 +74,7 @@ subroutine ftrsd3(s3,chansym0,rxdat,rxprob,rxdat2,rxprob2,ntrials0, &
numera=0 numera=0
workdat=rxdat workdat=rxdat
call rs_decode_sf(workdat,era_pos,numera,nerr) !Call the decoder call rs_decode_sf(workdat,era_pos,numera,nerr) !Call the decoder
nerr=-1
if(nerr.ge.0) then if(nerr.ge.0) then
! Hard-decision decoding succeeded. Save codeword and some parameters. ! Hard-decision decoding succeeded. Save codeword and some parameters.
@ -87,7 +88,6 @@ subroutine ftrsd3(s3,chansym0,rxdat,rxprob,rxdat2,rxprob2,ntrials0, &
param(5)=0 param(5)=0
param(7)=1000*1000 !??? param(7)=1000*1000 !???
ntry=0 ntry=0
! print*,'AA1',nerr
go to 900 go to 900
endif endif
@ -129,11 +129,6 @@ subroutine ftrsd3(s3,chansym0,rxdat,rxprob,rxdat2,rxprob2,ntrials0, &
j=indexes(NN-1-i) j=indexes(NN-1-i)
thresh=thresh0(i) thresh=thresh0(i)
! Generate a random number ir, 0 <= ir <= 100 (see POSIX.1-2001 example). ! Generate a random number ir, 0 <= ir <= 100 (see POSIX.1-2001 example).
! nseed=nseed*1103515245 + 12345
! ir=mod(nseed/65536,32768)
! ir=(100*ir)/32768
! nseed=iand(ir,2147483647)
ir=100.0*ran1(nseed) ir=100.0*ran1(nseed)
if((ir.lt.thresh) .and. numera.lt. 0.69*(NN-KK)) then if((ir.lt.thresh) .and. numera.lt. 0.69*(NN-KK)) then
era_pos(numera)=j era_pos(numera)=j
@ -144,7 +139,6 @@ subroutine ftrsd3(s3,chansym0,rxdat,rxprob,rxdat2,rxprob2,ntrials0, &
endif endif
enddo enddo
call rs_decode_sf(workdat,era_pos,numera,nerr) !Call the decoder call rs_decode_sf(workdat,era_pos,numera,nerr) !Call the decoder
if( nerr.ge.0) then if( nerr.ge.0) then
! We have a candidate codeword. Find its hard and soft distance from ! We have a candidate codeword. Find its hard and soft distance from
! the received word. Also find pp1 and pp2 from the full array ! the received word. Also find pp1 and pp2 from the full array
@ -163,6 +157,8 @@ subroutine ftrsd3(s3,chansym0,rxdat,rxprob,rxdat2,rxprob2,ntrials0, &
pp=0. pp=0.
call getpp3(s3,workdat,pp) call getpp3(s3,workdat,pp)
! write(*,5001) ncandidates,nhard,nsoft,ntotal,pp,pp1,pp2
!5001 format(4i8,3f7.3)
if(pp.gt.pp1) then if(pp.gt.pp1) then
pp2=pp1 pp2=pp1
pp1=pp pp1=pp
@ -191,6 +187,6 @@ subroutine ftrsd3(s3,chansym0,rxdat,rxprob,rxdat2,rxprob2,ntrials0, &
param(7)=1000.0*pp2 param(7)=1000.0*pp2
param(8)=1000.0*pp1 param(8)=1000.0*pp1
if(param(0).eq.0) param(2)=-1 if(param(0).eq.0) param(2)=-1
!write(*,*) ntry,ncandidates,nera_best,nhard_min,nsoft_min,ntotal_min,pp1,pp2
900 return 900 return
end subroutine ftrsd3 end subroutine ftrsd3

View File

@ -1,9 +1,10 @@
subroutine sfox_gen(idat,f0,fsample,cdat) subroutine sfox_gen(idat,f0,fsample,isync,cdat)
use sfox_mod use sfox_mod
complex cdat(NMAX) !Generated complex waveform complex cdat(NMAX) !Generated complex waveform
complex w,wstep complex w,wstep
integer idat(NN) integer idat(NN)
integer isync(50)
twopi=8.0*atan(1.0) twopi=8.0*atan(1.0)
tsync=NS*NSPS/fsample tsync=NS*NSPS/fsample

View File

@ -2,7 +2,6 @@ module sfox_mod
parameter (NMAX=15*12000) !Samples in iwave (180,000) parameter (NMAX=15*12000) !Samples in iwave (180,000)
integer MM,NQ,NN,KK,ND1,ND2,NFZ,NSPS,NS,NSYNC,NZ,NFFT,NFFT1 integer MM,NQ,NN,KK,ND1,ND2,NFZ,NSPS,NS,NSYNC,NZ,NFFT,NFFT1
integer isync(50)
contains contains
subroutine sfox_init(mm0,nn0,kk0,itu,fspread,delay,fsample,ts) subroutine sfox_init(mm0,nn0,kk0,itu,fspread,delay,fsample,ts)

View File

@ -1,11 +1,13 @@
subroutine sfox_sync(crcvd,fsample,f,t) subroutine sfox_sync(crcvd,fsample,isync,f,t,f1,xdt)
use sfox_mod use sfox_mod
complex crcvd(NMAX) !Signal as received complex crcvd(NMAX) !Signal as received
complex, allocatable :: c(:) !Work array complex, allocatable :: c(:) !Work array
integer isync(50)
real, allocatable :: s(:,:) !Symbol spectra, 1/8 symbol steps real, allocatable :: s(:,:) !Symbol spectra, 1/8 symbol steps
! character*1 line(-30:30),mark(0:5) real, allocatable :: ccf(:,:) !
! data mark/' ','.','-','+','X','$'/ character*1 line(-30:30),mark(0:6)
data mark/' ','.','-','+','X','$','#'/
nh=NFFT1/2 !1024 nh=NFFT1/2 !1024
istep=nh/8 !128 istep=nh/8 !128
@ -16,6 +18,7 @@ subroutine sfox_sync(crcvd,fsample,f,t)
allocate(c(0:nfft1-1)) allocate(c(0:nfft1-1))
allocate(s(nh/2,nsz)) allocate(s(nh/2,nsz))
! Compute symbol spectra with df=baud/2 and 1/8 symbol steps.
ia=1-istep ia=1-istep
fac=1.0/NFFT1 fac=1.0/NFFT1
do j=1,nsz do j=1,nsz
@ -35,7 +38,9 @@ subroutine sfox_sync(crcvd,fsample,f,t)
i0=nint(1500.0/df) i0=nint(1500.0/df)
ipk=-999 ipk=-999
jpk=-999 jpk=-999
do j=1,nsz-8*NS jz=nsz-8*NS
allocate(ccf(-iz:iz,1:jz))
do j=1,jz
do i=-iz,iz do i=-iz,iz
p=0. p=0.
do k=1,NS do k=1,NS
@ -43,6 +48,7 @@ subroutine sfox_sync(crcvd,fsample,f,t)
jj=j + 8*(k-1) jj=j + 8*(k-1)
p=p + s(ii,jj) p=p + s(ii,jj)
enddo enddo
ccf(i,j)=p
if(p.gt.pmax) then if(p.gt.pmax) then
pmax=p pmax=p
ipk=i ipk=i
@ -54,6 +60,23 @@ subroutine sfox_sync(crcvd,fsample,f,t)
dfreq=ipk*df dfreq=ipk*df
f=1500.0+dfreq f=1500.0+dfreq
t=(jpk-201)*istep/fsample t=(jpk-201)*istep/fsample
if(NS.ne.-99) go to 900
return ferr=f-f1
terr=t-xdt
if(abs(ferr).lt.5.357 .and. abs(terr).lt.0.0233) go to 900
ccf=ccf/pmax
do j=jpk-10,jpk+10
do i=-iz,iz
k=6.001*ccf(i,j)
line(i)=mark(k)
enddo
write(*,1000) j,line(-iz:iz)
1000 format(i5,2x,61a1)
enddo
write(*,1100) ferr,terr
1100 format('ferr:',f7.1,' terr:',f7.2)
900 return
end subroutine sfox_sync end subroutine sfox_sync

View File

@ -10,6 +10,7 @@ program sfoxtest
type(hdr) h !Header for .wav file type(hdr) h !Header for .wav file
integer*2 iwave(NMAX) !Generated i*2 waveform integer*2 iwave(NMAX) !Generated i*2 waveform
integer param(0:8) integer param(0:8)
integer isync(50)
real*4 xnoise(NMAX) !Random noise real*4 xnoise(NMAX) !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
@ -108,6 +109,7 @@ program sfoxtest
! Generate a sync pattern ! Generate a sync pattern
do i=1,NS do i=1,NS
isync(i)=NQ*ran1(idummy) isync(i)=NQ*ran1(idummy)
if(i.gt.20) isync(i)=NQ/2
enddo enddo
! Generate a message ! Generate a message
@ -124,7 +126,7 @@ program sfoxtest
! Generate cdat, the SuperFox waveform ! Generate cdat, the SuperFox waveform
call timer('gen ',0) call timer('gen ',0)
call sfox_gen(chansym0,f0,fsample,cdat) call sfox_gen(chansym0,f0,fsample,isync,cdat)
call timer('gen ',1) call timer('gen ',1)
isnr0=-8 isnr0=-8
@ -158,7 +160,7 @@ program sfoxtest
f1=1500.0 + 20.0*(ran1(idummy)-0.5) f1=1500.0 + 20.0*(ran1(idummy)-0.5)
xdt=0.3*ran1(idummy) xdt=0.3*ran1(idummy)
call timer('gen ',0) call timer('gen ',0)
call sfox_gen(chansym0,f1,fsample,cdat) call sfox_gen(chansym0,f1,fsample,isync,cdat)
call timer('gen ',1) call timer('gen ',1)
endif endif
@ -181,7 +183,7 @@ program sfoxtest
else else
! Find signal freq and DT ! Find signal freq and DT
call timer('sync ',0) call timer('sync ',0)
call sfox_sync(crcvd,fsample,f,t) call sfox_sync(crcvd,fsample,isync,f,t,f1,xdt)
call timer('sync ',1) call timer('sync ',1)
endif endif
ferr=f-f1 ferr=f-f1
@ -234,7 +236,6 @@ program sfoxtest
close(10) close(10)
endif endif
! if(nharderr.le.maxerr) ngood=ngood+1
if(count(correct.ne.chansym0).eq.0) ngood=ngood+1 if(count(correct.ne.chansym0).eq.0) ngood=ngood+1
enddo ! ifile enddo ! ifile
fgoodsync=float(ngoodsync)/nfiles fgoodsync=float(ngoodsync)/nfiles