ft8d/ft8d.f90

105 lines
3.1 KiB
Fortran
Raw Normal View History

2018-03-24 07:20:34 -04:00
program ft8d
! Decode FT8 data read from *.c2 files.
2018-03-24 07:20:34 -04:00
include 'ft8_params.f90'
character infile*80,datetime*13,message*22,msg37*37
character*22 allmessages(100)
character*12 mycall12,hiscall12
character*6 mygrid6,hisgrid6
2018-04-01 11:36:02 -04:00
real s(NFFT1,NHSYM)
real sbase(NFFT1)
real candidate(3,200)
2018-04-01 11:36:02 -04:00
real*8 dialfreq
complex dd(NMAX)
2018-03-24 07:20:34 -04:00
logical newdat,lsubtract,ldupe,bcontest
integer apsym(KK)
2018-03-24 07:20:34 -04:00
integer allsnrs(100)
save s,dd
nargs=iargc()
if(nargs.lt.1) then
2018-03-24 12:06:33 -04:00
print*,'Usage: ft8d file1 [file2 ...]'
go to 999
2018-03-24 07:20:34 -04:00
endif
nfiles=nargs
twopi=8.0*atan(1.0)
2018-04-01 11:36:02 -04:00
fs=6000.0 !Sample rate
2018-03-24 07:20:34 -04:00
dt=1.0/fs !Sample interval (s)
tt=NSPS*dt !Duration of "itone" symbols (s)
ts=2*NSPS*dt !Duration of OQPSK symbols (s)
baud=1.0/tt !Keying rate (baud)
txt=NZ*dt !Transmission length (s)
2018-04-01 11:36:02 -04:00
nfa=-2000
nfb=+2000
nfqso=0
2018-03-24 07:20:34 -04:00
do ifile=1,nfiles
2018-03-24 12:06:33 -04:00
call getarg(ifile,infile)
open(10,file=infile,status='old',access='stream')
2018-04-01 11:36:02 -04:00
read(10,end=999) dialfreq,dd
2018-03-24 12:06:33 -04:00
close(10)
j2=index(infile,'.c2')
2018-03-24 12:06:33 -04:00
read(infile(j2-6:j2-1),*) nutc
datetime=infile(j2-13:j2-1)
ndecodes=0
allmessages=' '
allsnrs=0
2018-03-26 02:37:27 -04:00
ndepth=1
npass=1
do ipass=1,npass
2018-03-24 12:06:33 -04:00
newdat=.true.
syncmin=1.5
if(ipass.eq.1) then
lsubtract=.true.
if(ndepth.eq.1) lsubtract=.false.
elseif(ipass.eq.2) then
n2=ndecodes
if(ndecodes.eq.0) cycle
lsubtract=.true.
elseif(ipass.eq.3) then
if((ndecodes-n2).eq.0) cycle
lsubtract=.false.
endif
2018-04-01 11:36:02 -04:00
call sync8(dd,nfa+3000,nfb+3000,syncmin,nfqso+3000,s,candidate,ncand,sbase)
2018-03-24 12:06:33 -04:00
do icand=1,ncand
sync=candidate(3,icand)
f1=candidate(1,icand)
xdt=candidate(2,icand)
xbase=10.0**(0.1*(sbase(nint(f1/3.125))-40.0))
nsnr0=min(99,nint(10.0*log10(sync) - 25.5)) ! ### empirical ###
2018-04-01 11:36:02 -04:00
call ft8b(dd,newdat,nQSOProgress,nfqso+3000,nftx,ndepth,lft8apon, &
2018-03-24 12:06:33 -04:00
lapcqonly,napwid,lsubtract,nagain,iaptype,mycall12,mygrid6, &
hiscall12,bcontest,sync,f1,xdt,xbase,apsym,nharderrors,dmin, &
nbadcrc,iappass,iera,msg37,xsnr)
message=msg37(1:22)
nsnr=nint(xsnr)
xdt=xdt-0.5
hd=nharderrors+dmin
if(nbadcrc.eq.0) then
if(bcontest) then
call fix_contest_msg(mygrid6,message)
msg37(1:22)=message
endif
ldupe=.false.
do id=1,ndecodes
if(message.eq.allmessages(id).and.nsnr.le.allsnrs(id)) ldupe=.true.
enddo
if(.not.ldupe) then
ndecodes=ndecodes+1
allmessages(ndecodes)=message
allsnrs(ndecodes)=nsnr
2018-03-24 07:20:34 -04:00
endif
2018-04-01 12:05:05 -04:00
write(*,1004) nutc,ipass,iaptype,iappass, &
2018-03-24 12:06:33 -04:00
nharderrors,dmin,hd,min(sync,999.0),nint(xsnr), &
2018-04-01 11:36:02 -04:00
xdt,nint(f1-3000+dialfreq),message
2018-04-01 12:05:05 -04:00
1004 format(i6.6,3i2,i3,3f6.1,i4,f6.2,i9,1x,a22)
2018-03-24 12:06:33 -04:00
endif
2018-03-24 07:20:34 -04:00
enddo
2018-03-24 12:06:33 -04:00
enddo
enddo ! ifile loop
2018-03-24 07:20:34 -04:00
999 end program ft8d