2017-11-09 15:23:04 -05:00
|
|
|
program fox_sim
|
|
|
|
|
|
|
|
! Simulates QSO exchanges using the proposed FT8 "DXpedition" mode.
|
|
|
|
parameter (MAXSIG=5,NCALLS=268)
|
|
|
|
character*6 xcall(NCALLS)
|
|
|
|
character*4 xgrid(NCALLS)
|
|
|
|
integer isnr(NCALLS)
|
|
|
|
|
|
|
|
character*32 fmsg(MAXSIG),fm
|
|
|
|
character*22 hmsg(MAXSIG),hm
|
|
|
|
character*16 log
|
|
|
|
character*6 called(MAXSIG)
|
|
|
|
character*4 gcalled(MAXSIG)
|
|
|
|
character*6 MyCall
|
|
|
|
character*4 MyGrid
|
|
|
|
character*8 arg
|
2017-11-09 21:14:26 -05:00
|
|
|
character*1 c1,c2,c3,c4
|
2017-11-09 15:23:04 -05:00
|
|
|
integer ntot(MAXSIG),irate(MAXSIG),ntimes(MAXSIG)
|
|
|
|
logical logit
|
|
|
|
common/dxpfifo/nc,isnr,xcall,xgrid
|
|
|
|
|
|
|
|
nargs=iargc()
|
|
|
|
if(nargs.ne.2 .and. nargs.ne.4) then
|
|
|
|
print*,'Usage: fox_sim nseq maxtimes'
|
2017-11-09 16:15:37 -05:00
|
|
|
print*,' fox_sim nseq maxtimes nsig fail'
|
|
|
|
print*,' '
|
|
|
|
print*,' nseq: number of T/R sequences to execute'
|
|
|
|
print*,' maxtimes: number of repeats of same Tx message'
|
|
|
|
print*,' nsig: number of simultaneous Tx sigals'
|
|
|
|
print*,' fail: receiving error rate'
|
2017-11-09 15:23:04 -05:00
|
|
|
go to 999
|
|
|
|
endif
|
|
|
|
ii1=1
|
|
|
|
ii2=5
|
|
|
|
jj1=0
|
|
|
|
jj2=5
|
|
|
|
nseq=80
|
|
|
|
if(nargs.ge.2) then
|
|
|
|
call getarg(1,arg)
|
|
|
|
read(arg,*) nseq
|
|
|
|
call getarg(2,arg)
|
|
|
|
read(arg,*) maxtimes
|
|
|
|
endif
|
|
|
|
if(nargs.eq.4) then
|
|
|
|
call getarg(3,arg)
|
|
|
|
read(arg,*) nsig
|
|
|
|
call getarg(4,arg)
|
|
|
|
read(arg,*) fail
|
|
|
|
ii1=nsig
|
|
|
|
ii2=nsig
|
|
|
|
jj1=nint(10*fail)
|
|
|
|
jj2=nint(10*fail)
|
|
|
|
endif
|
|
|
|
|
|
|
|
! Read a file with calls and grids; insert random S/N values.
|
|
|
|
! This is used in place of an operator-selected FIFO
|
2017-11-10 10:02:47 -05:00
|
|
|
open(10,file='xcall.txt',status='old')
|
2017-11-09 15:23:04 -05:00
|
|
|
do i=1,NCALLS
|
2017-11-10 10:02:47 -05:00
|
|
|
read(10,1000) xcall(i),xgrid(i)
|
|
|
|
1000 format(a6,7x,a4)
|
|
|
|
if(i.ne.-99) cycle
|
2017-11-09 21:14:26 -05:00
|
|
|
j=mod(i-1,26)
|
|
|
|
c1=char(ichar('A')+j)
|
|
|
|
k=mod((i-1)/26,26)
|
|
|
|
c2=char(ichar('A')+k)
|
|
|
|
n=mod((i-1)/260,10)
|
|
|
|
c3=char(ichar('0')+n)
|
|
|
|
xcall(i)='K'//c2//c3//c1//c1//c1
|
|
|
|
|
|
|
|
j=mod(i-1,18)
|
|
|
|
c1=char(ichar('A')+j)
|
|
|
|
k=mod((i-1)/18,18)
|
|
|
|
c2=char(ichar('A')+k)
|
|
|
|
n=mod((i-1)/10,10)
|
|
|
|
c4=char(ichar('0')+n)
|
|
|
|
n=mod((i-1)/100,10)
|
|
|
|
c3=char(ichar('0')+n)
|
|
|
|
xgrid(i)=c1//c2//c3//c4
|
|
|
|
|
2017-11-09 15:23:04 -05:00
|
|
|
call random_number(x)
|
|
|
|
isnr(i)=-20+int(40*x)
|
|
|
|
enddo
|
2017-11-09 21:14:26 -05:00
|
|
|
! close(10)
|
2017-11-09 15:23:04 -05:00
|
|
|
|
2017-11-09 16:15:37 -05:00
|
|
|
! Write headings for the summary file
|
2017-11-09 15:23:04 -05:00
|
|
|
minutes=nseq/4
|
|
|
|
write(13,1002) nseq,minutes,maxtimes
|
2017-11-09 15:45:36 -05:00
|
|
|
1002 format(/'Nseq:',i4,' Minutes:',i3,' Maxtimes:',i2// &
|
|
|
|
18x,'Logged QSOs',22x,'Rate (QSOs/hour)'/ &
|
|
|
|
'fail Nsig: 1 2 3 4 5 1 2 3 4 5'/ &
|
|
|
|
71('-'))
|
2017-11-09 15:23:04 -05:00
|
|
|
|
2017-11-10 10:02:47 -05:00
|
|
|
write(*,1003)
|
|
|
|
1003 format('Seq s n Fox messages Hound messages Logged info i Rate'/87('-'))
|
|
|
|
|
2017-11-09 15:23:04 -05:00
|
|
|
ntot=0
|
|
|
|
irate=0
|
|
|
|
MyCall='KH1DX'
|
|
|
|
MyGrid='AJ10'
|
|
|
|
|
2017-11-09 16:15:37 -05:00
|
|
|
do jj=jj1,jj2 !Loop over Rx failure rates
|
2017-11-09 15:23:04 -05:00
|
|
|
fail=0.1*jj
|
2017-11-09 16:15:37 -05:00
|
|
|
do ii=ii1,ii2 !Loop over range of nsig
|
2017-11-09 15:23:04 -05:00
|
|
|
nc=0 !Set FIFO pointer to top
|
|
|
|
ntimes=1
|
|
|
|
nsig=ii
|
|
|
|
nlogged=0
|
|
|
|
fmsg="CQ KH1DX AJ10"
|
|
|
|
hmsg=""
|
|
|
|
called=" "
|
2017-11-09 16:15:37 -05:00
|
|
|
do iseq=0,nseq !Loop over specified number of sequences
|
2017-11-09 15:23:04 -05:00
|
|
|
if(iand(iseq,1).eq.0) then
|
2017-11-09 16:15:37 -05:00
|
|
|
do j=1,nsig !Loop over Fox's Tx slots
|
2017-11-09 15:23:04 -05:00
|
|
|
fm=fmsg(j)
|
|
|
|
hm=hmsg(j)
|
2017-11-09 16:15:37 -05:00
|
|
|
|
|
|
|
! Call fox_tx to determine the next Tx message for this slot
|
2017-11-09 15:23:04 -05:00
|
|
|
call fox_tx(maxtimes,fail,called(j),gcalled(j),hm,fm, &
|
|
|
|
ntimes(j),log,logit)
|
2017-11-09 16:15:37 -05:00
|
|
|
|
2017-11-09 15:23:04 -05:00
|
|
|
fmsg(j)=fm
|
|
|
|
if(logit) then
|
2017-11-09 16:15:37 -05:00
|
|
|
! Log this QSO
|
2017-11-09 15:23:04 -05:00
|
|
|
nlogged=nlogged+1
|
|
|
|
nrate=0
|
|
|
|
if(iseq.gt.0) nrate=nint(nlogged*240.0/iseq)
|
|
|
|
write(*,1010) iseq,j,ntimes(j),fmsg(j),log,nlogged,nrate
|
|
|
|
1010 format(i4.4,2i2,1x,a32,20x,a16,2i4)
|
2017-11-09 16:15:37 -05:00
|
|
|
! call log_routine()
|
2017-11-09 15:23:04 -05:00
|
|
|
else
|
|
|
|
write(*,1010) iseq,j,ntimes(j),fmsg(j)
|
|
|
|
endif
|
|
|
|
enddo
|
2017-11-09 16:15:37 -05:00
|
|
|
! call transmit()
|
2017-11-09 15:23:04 -05:00
|
|
|
endif
|
|
|
|
|
|
|
|
if(iand(iseq,1).eq.1) then
|
2017-11-09 16:15:37 -05:00
|
|
|
do j=1,nsig !Listen for expected responses
|
2017-11-09 15:23:04 -05:00
|
|
|
fm=fmsg(j)
|
|
|
|
call fox_rx(fail,called(j),fm,hm)
|
2017-11-09 16:15:37 -05:00
|
|
|
if(j.ge.2) then
|
|
|
|
if(hm.eq.hmsg(j-1)) hm=""
|
|
|
|
endif
|
2017-11-09 15:23:04 -05:00
|
|
|
hmsg(j)=hm
|
|
|
|
write(*,1020) iseq,j,hmsg(j)
|
|
|
|
1020 format(i4.4,i2,37x,a22)
|
|
|
|
enddo
|
|
|
|
endif
|
2017-11-10 10:02:47 -05:00
|
|
|
write(*,1021)
|
|
|
|
1021 format(87('-'))
|
2017-11-09 15:23:04 -05:00
|
|
|
enddo
|
|
|
|
ntot(ii)=nlogged
|
|
|
|
irate(ii)=0
|
|
|
|
if(iseq.gt.0) irate(ii)=nint(nlogged*3600.0/(15*iseq))
|
2017-11-09 15:45:36 -05:00
|
|
|
write(*,1030) nsig,fail,nlogged,nc
|
2017-11-09 16:15:37 -05:00
|
|
|
1030 format(/'Nsig:',i3,' Fail:',f4.1,' Logged QSOs:',i4, &
|
2017-11-09 15:45:36 -05:00
|
|
|
' Final nc:',i4)
|
2017-11-09 15:23:04 -05:00
|
|
|
enddo
|
2017-11-09 16:33:20 -05:00
|
|
|
|
|
|
|
! Write the summary file
|
2017-11-09 15:23:04 -05:00
|
|
|
write(13,1100) fail,ntot,irate
|
2017-11-09 15:45:36 -05:00
|
|
|
1100 format(f4.1,2x,5i6,5x,5i6)
|
2017-11-09 15:23:04 -05:00
|
|
|
enddo
|
|
|
|
|
|
|
|
999 end program fox_sim
|