2020-10-25 13:58:18 -04:00
|
|
|
module q65_decode
|
2020-08-01 09:24:59 -04:00
|
|
|
|
2021-04-28 10:13:42 -04:00
|
|
|
integer nsnr0,nfreq0
|
|
|
|
real xdt0
|
|
|
|
character msg0*37,cq0*3
|
|
|
|
|
2021-01-12 11:28:46 -05:00
|
|
|
type :: q65_decoder
|
|
|
|
procedure(q65_decode_callback), pointer :: callback
|
2020-08-01 09:24:59 -04:00
|
|
|
contains
|
2021-01-12 11:28:46 -05:00
|
|
|
procedure :: decode
|
|
|
|
end type q65_decoder
|
2020-08-01 09:24:59 -04:00
|
|
|
|
2021-01-12 11:28:46 -05:00
|
|
|
abstract interface
|
2021-01-13 10:55:01 -05:00
|
|
|
subroutine q65_decode_callback (this,nutc,snr1,nsnr,dt,freq, &
|
2021-01-19 15:30:17 -05:00
|
|
|
decoded,idec,nused,ntrperiod)
|
2021-01-12 11:28:46 -05:00
|
|
|
import q65_decoder
|
|
|
|
implicit none
|
|
|
|
class(q65_decoder), intent(inout) :: this
|
|
|
|
integer, intent(in) :: nutc
|
2021-01-13 10:55:01 -05:00
|
|
|
real, intent(in) :: snr1
|
2021-01-12 11:28:46 -05:00
|
|
|
integer, intent(in) :: nsnr
|
|
|
|
real, intent(in) :: dt
|
|
|
|
real, intent(in) :: freq
|
|
|
|
character(len=37), intent(in) :: decoded
|
2021-01-14 13:23:09 -05:00
|
|
|
integer, intent(in) :: idec
|
2021-01-19 15:30:17 -05:00
|
|
|
integer, intent(in) :: nused
|
2021-01-12 11:28:46 -05:00
|
|
|
integer, intent(in) :: ntrperiod
|
|
|
|
end subroutine q65_decode_callback
|
|
|
|
end interface
|
2020-08-01 09:24:59 -04:00
|
|
|
|
|
|
|
contains
|
|
|
|
|
2021-05-27 12:20:20 -04:00
|
|
|
subroutine decode(this,callback,iwave,nqd0,nutc,ntrperiod,nsubmode,nfqso, &
|
2021-05-30 12:07:48 -04:00
|
|
|
ntol,ndepth,nfa0,nfb0,lclearave,single_decode,lagain,max_drift0, &
|
|
|
|
lnewdat0,emedelay,mycall,hiscall,hisgrid,nQSOprogress,ncontest, &
|
2023-02-12 17:33:21 -05:00
|
|
|
lapcqonly,navg0,nqf)
|
2020-08-01 09:24:59 -04:00
|
|
|
|
2021-01-14 13:13:40 -05:00
|
|
|
! Top-level routine that organizes the decoding of Q65 signals
|
2020-10-09 13:16:25 -04:00
|
|
|
! Input: iwave Raw data, i*2
|
|
|
|
! nutc UTC for time-tagging the decode
|
|
|
|
! ntrperiod T/R sequence length (s)
|
|
|
|
! nsubmode Tone-spacing indicator, 0-4 for A-E
|
|
|
|
! nfqso Target signal frequency (Hz)
|
|
|
|
! ntol Search range around nfqso (Hz)
|
2020-11-11 11:14:02 -05:00
|
|
|
! ndepth Optional decoding level
|
2021-01-14 13:13:40 -05:00
|
|
|
! lclearave Flag to clear the message-averaging arrays
|
|
|
|
! emedelay Sync search extended to cover EME delays
|
|
|
|
! nQSOprogress Auto-sequencing state for the present QSO
|
|
|
|
! ncontest Supported contest type
|
|
|
|
! lapcqonly Flag to use AP only for CQ calls
|
2020-10-09 13:16:25 -04:00
|
|
|
! Output: sent to the callback routine for display to user
|
|
|
|
|
2020-08-01 09:24:59 -04:00
|
|
|
use timer_module, only: timer
|
2020-10-27 13:08:07 -04:00
|
|
|
use packjt77
|
2020-08-01 09:24:59 -04:00
|
|
|
use, intrinsic :: iso_c_binding
|
2020-12-28 15:27:10 -05:00
|
|
|
use q65 !Shared variables
|
2021-01-28 13:01:52 -05:00
|
|
|
use prog_args
|
2023-02-07 15:17:09 -05:00
|
|
|
use types
|
2020-12-27 15:27:26 -05:00
|
|
|
|
2023-02-07 15:17:09 -05:00
|
|
|
parameter (NMAX=300*12000) !Max TRperiod is 300 s
|
|
|
|
parameter (MAX_CALLERS=40) !For multiple q3 decodes in NA VHf Contest mode
|
|
|
|
|
2020-10-25 13:58:18 -04:00
|
|
|
class(q65_decoder), intent(inout) :: this
|
2023-02-07 15:17:09 -05:00
|
|
|
|
2020-10-25 13:58:18 -04:00
|
|
|
procedure(q65_decode_callback) :: callback
|
2020-10-09 13:16:25 -04:00
|
|
|
character(len=12) :: mycall, hiscall !Used for AP decoding
|
2020-08-01 09:24:59 -04:00
|
|
|
character(len=6) :: hisgrid
|
2020-10-09 13:16:25 -04:00
|
|
|
character*37 decoded !Decoded message
|
2021-11-02 15:17:51 -04:00
|
|
|
character*37 decodes(100)
|
2020-10-27 13:08:07 -04:00
|
|
|
character*77 c77
|
2020-10-30 11:07:44 -04:00
|
|
|
character*78 c78
|
2021-01-19 15:30:17 -05:00
|
|
|
character*6 cutc
|
2021-02-02 09:27:40 -05:00
|
|
|
character c6*6,c4*4,cmode*4
|
|
|
|
character*80 fmt
|
2020-08-08 09:14:12 -04:00
|
|
|
integer*2 iwave(NMAX) !Raw data
|
2020-10-17 13:16:46 -04:00
|
|
|
real, allocatable :: dd(:) !Raw data
|
2023-02-12 17:33:21 -05:00
|
|
|
real xdtdecodes(100)
|
2023-01-04 12:02:10 -05:00
|
|
|
real f0decodes(100)
|
2020-10-27 13:22:02 -04:00
|
|
|
integer dat4(13) !Decoded message as 12 6-bit integers
|
2020-11-22 13:58:29 -05:00
|
|
|
integer dgen(13)
|
2023-02-12 17:33:21 -05:00
|
|
|
integer nqf(20)
|
2023-02-07 15:17:09 -05:00
|
|
|
integer stageno !Added by W3SZ
|
|
|
|
integer time
|
2021-01-23 10:58:28 -05:00
|
|
|
logical lclearave,lnewdat0,lapcqonly,unpk77_success
|
2023-02-12 17:33:21 -05:00
|
|
|
logical single_decode,lagain
|
2020-10-09 13:16:25 -04:00
|
|
|
complex, allocatable :: c00(:) !Analytic signal, 6000 Sa/s
|
|
|
|
complex, allocatable :: c0(:) !Analytic signal, 6000 Sa/s
|
2023-02-07 15:17:09 -05:00
|
|
|
type(q3list) callers(MAX_CALLERS)
|
2023-02-15 11:49:12 -05:00
|
|
|
|
2021-01-14 13:13:40 -05:00
|
|
|
! Start by setting some parameters and allocating storage for large arrays
|
2021-01-28 13:01:52 -05:00
|
|
|
call sec0(0,tdecode)
|
2023-02-07 15:17:09 -05:00
|
|
|
stageno=0
|
2021-11-02 15:17:51 -04:00
|
|
|
ndecodes=0
|
|
|
|
decodes=' '
|
2023-01-04 12:02:10 -05:00
|
|
|
f0decodes=0.
|
2023-02-12 17:33:21 -05:00
|
|
|
xdtdecodes=0.
|
2021-01-16 12:21:13 -05:00
|
|
|
nfa=nfa0
|
|
|
|
nfb=nfb0
|
2021-05-27 12:20:20 -04:00
|
|
|
nqd=nqd0
|
2021-01-23 10:58:28 -05:00
|
|
|
lnewdat=lnewdat0
|
2021-05-30 12:07:48 -04:00
|
|
|
max_drift=max_drift0
|
2020-12-30 16:12:02 -05:00
|
|
|
idec=-1
|
2021-01-28 13:01:52 -05:00
|
|
|
idf=0
|
|
|
|
idt=0
|
2021-02-08 09:24:16 -05:00
|
|
|
nrc=-2
|
2021-01-13 11:21:59 -05:00
|
|
|
mode_q65=2**nsubmode
|
2020-11-15 12:21:08 -05:00
|
|
|
npts=ntrperiod*12000
|
2020-08-08 09:14:12 -04:00
|
|
|
nfft1=ntrperiod*12000
|
|
|
|
nfft2=ntrperiod*6000
|
2021-05-20 12:57:41 -04:00
|
|
|
npasses=1
|
2023-02-21 09:44:56 -05:00
|
|
|
nhist2=0
|
2021-11-01 14:57:52 -04:00
|
|
|
if(lagain) ndepth=ior(ndepth,3) !Use 'Deep' for manual Q65 decodes
|
2021-10-17 15:26:57 -04:00
|
|
|
dxcall13=hiscall ! initialize for use in packjt77
|
|
|
|
mycall13=mycall
|
2023-02-07 15:17:09 -05:00
|
|
|
if(ncontest.eq.1) then
|
2023-02-15 11:49:12 -05:00
|
|
|
! NA VHF, WW-Digi, or ARRL Digi Contest
|
2023-03-02 14:10:18 -05:00
|
|
|
open(24,file=trim(data_dir)//'/tsil.3q',status='unknown', &
|
|
|
|
form='unformatted')
|
|
|
|
read(24,end=2) nhist2
|
2023-02-20 14:19:38 -05:00
|
|
|
if(nhist2.ge.1 .and. nhist2.le.40) then
|
2023-03-02 14:10:18 -05:00
|
|
|
read(24,end=2) callers(1:nhist2)
|
2023-02-20 14:19:38 -05:00
|
|
|
now=time()
|
|
|
|
do i=1,nhist2
|
|
|
|
hours=(now - callers(i)%nsec)/3600.0
|
|
|
|
if(hours.gt.24.0) then
|
|
|
|
callers(i:nhist2-1)=callers(i+1:nhist2)
|
|
|
|
nhist2=nhist2-1
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
else
|
|
|
|
nhist2=0
|
|
|
|
endif
|
2023-02-16 16:50:24 -05:00
|
|
|
2 close(24)
|
2023-02-07 15:17:09 -05:00
|
|
|
endif
|
2021-10-17 15:26:57 -04:00
|
|
|
|
2021-01-19 15:30:17 -05:00
|
|
|
! Determine the T/R sequence: iseq=0 (even), or iseq=1 (odd)
|
2023-02-16 16:50:24 -05:00
|
|
|
n=nutc
|
2021-03-05 13:28:14 -05:00
|
|
|
if(ntrperiod.ge.60 .and. nutc.le.2359) n=100*n
|
2021-01-19 15:30:17 -05:00
|
|
|
write(cutc,'(i6.6)') n
|
|
|
|
read(cutc,'(3i2)') ih,im,is
|
|
|
|
nsec=3600*ih + 60*im + is
|
|
|
|
iseq=mod(nsec/ntrperiod,2)
|
|
|
|
|
2021-01-14 14:56:37 -05:00
|
|
|
if(lclearave) call q65_clravg
|
2020-11-15 12:21:08 -05:00
|
|
|
allocate(dd(npts))
|
2020-10-08 16:48:11 -04:00
|
|
|
allocate (c00(0:nfft1-1))
|
2020-08-08 13:57:24 -04:00
|
|
|
allocate (c0(0:nfft1-1))
|
2020-08-09 11:04:49 -04:00
|
|
|
|
2021-03-18 16:33:46 -04:00
|
|
|
if(lagain) then
|
|
|
|
call q65_hist(nfqso,dxcall=hiscall,dxgrid=hisgrid)
|
|
|
|
endif
|
|
|
|
|
2021-02-05 14:14:22 -05:00
|
|
|
nsps=1800
|
|
|
|
if(ntrperiod.eq.30) then
|
2020-08-08 09:14:12 -04:00
|
|
|
nsps=3600
|
|
|
|
else if(ntrperiod.eq.60) then
|
2020-10-25 14:10:38 -04:00
|
|
|
nsps=7200
|
2020-08-08 09:14:12 -04:00
|
|
|
else if(ntrperiod.eq.120) then
|
|
|
|
nsps=16000
|
|
|
|
else if(ntrperiod.eq.300) then
|
|
|
|
nsps=41472
|
2020-10-09 14:12:34 -04:00
|
|
|
endif
|
2021-01-08 09:42:07 -05:00
|
|
|
|
2020-10-09 14:12:34 -04:00
|
|
|
baud=12000.0/nsps
|
2020-10-29 10:53:30 -04:00
|
|
|
this%callback => callback
|
2020-10-09 14:12:34 -04:00
|
|
|
nFadingModel=1
|
2023-01-24 15:07:55 -05:00
|
|
|
|
2023-02-10 13:09:47 -05:00
|
|
|
! ibwa=max(1,int(1.8*log(baud*mode_q65)) + 5)
|
|
|
|
!### This needs work!
|
2023-02-10 14:31:45 -05:00
|
|
|
ibwa=1 !Q65-60A
|
2023-02-10 13:09:47 -05:00
|
|
|
if(mode_q65.eq.2) ibwa=3 !Q65-60B
|
|
|
|
if(mode_q65.eq.4) ibwa=8 !Q65-60C
|
2023-06-23 12:56:33 -04:00
|
|
|
if(mode_q65.eq.8) ibwa=8 !Q65-60D
|
|
|
|
if(mode_q65.eq.16) ibwa=8 !Q65-60E
|
2023-02-10 13:09:47 -05:00
|
|
|
!###
|
|
|
|
|
2023-02-11 14:08:10 -05:00
|
|
|
! ibwb=min(15,ibwa+4)
|
|
|
|
ibwb=min(15,ibwa+6)
|
2023-01-23 14:03:49 -05:00
|
|
|
maxiters=40
|
|
|
|
if(iand(ndepth,3).eq.2) maxiters=60
|
2021-10-20 11:18:31 -04:00
|
|
|
if(iand(ndepth,3).eq.3) then
|
2023-01-23 14:03:49 -05:00
|
|
|
ibwa=max(1,ibwa-2)
|
2023-06-23 12:56:33 -04:00
|
|
|
ibwb=min(15,ibwb+2)
|
2023-01-23 14:03:49 -05:00
|
|
|
maxiters=100
|
2021-01-08 09:42:07 -05:00
|
|
|
endif
|
2023-01-24 15:07:55 -05:00
|
|
|
|
2021-04-30 08:31:45 -04:00
|
|
|
! Generate codewords for full-AP list decoding
|
|
|
|
if(ichar(hiscall(1:1)).eq.0) hiscall=' '
|
|
|
|
if(ichar(hisgrid(1:1)).eq.0) hisgrid=' '
|
2021-05-13 15:33:52 -04:00
|
|
|
ncw=0
|
2023-02-12 17:33:21 -05:00
|
|
|
if(nqd.eq.1 .or. lagain .or. ncontest.eq.1) then
|
2023-02-07 15:17:09 -05:00
|
|
|
if(ncontest.eq.1) then
|
2023-02-11 14:08:10 -05:00
|
|
|
call q65_set_list2(mycall,hiscall,hisgrid,callers,nhist2, &
|
|
|
|
codewords,ncw)
|
2023-02-07 15:17:09 -05:00
|
|
|
else
|
|
|
|
call q65_set_list(mycall,hiscall,hisgrid,codewords,ncw)
|
|
|
|
endif
|
2021-05-13 15:33:52 -04:00
|
|
|
endif
|
2020-11-30 09:52:47 -05:00
|
|
|
dgen=0
|
2020-12-28 15:27:10 -05:00
|
|
|
call q65_enc(dgen,codewords) !Initialize the Q65 codec
|
2021-01-14 14:56:37 -05:00
|
|
|
nused=1
|
2021-01-14 15:39:48 -05:00
|
|
|
iavg=0
|
2021-11-09 11:00:55 -05:00
|
|
|
|
|
|
|
! W3SZ patch: Initialize AP params here, rather than afer the call to ana64().
|
|
|
|
call ft8apset(mycall,hiscall,ncontest,apsym0,aph10) ! Generate ap symbols
|
|
|
|
where(apsym0.eq.-1) apsym0=0
|
|
|
|
npasses=2
|
|
|
|
if(nQSOprogress.eq.5) npasses=3
|
|
|
|
|
2021-01-13 14:34:20 -05:00
|
|
|
call timer('q65_dec0',0)
|
2021-06-08 11:16:26 -04:00
|
|
|
! Call top-level routine in q65 module: establish sync and try for a
|
2021-06-23 13:58:08 -04:00
|
|
|
! q3 or q0 decode.
|
2023-01-23 19:22:34 -05:00
|
|
|
call q65_dec0(iavg,iwave,ntrperiod,nfqso,ntol,lclearave, &
|
2021-10-11 14:56:08 -04:00
|
|
|
emedelay,xdt,f0,snr1,width,dat4,snr2,idec,stageno)
|
2021-01-13 14:34:20 -05:00
|
|
|
call timer('q65_dec0',1)
|
2021-01-14 13:13:40 -05:00
|
|
|
|
2020-12-29 16:41:48 -05:00
|
|
|
if(idec.ge.0) then
|
2021-06-08 11:16:26 -04:00
|
|
|
dtdec=xdt !We have a q3 or q0 decode at nfqso
|
2021-01-19 14:11:21 -05:00
|
|
|
f0dec=f0
|
2020-12-29 16:41:48 -05:00
|
|
|
go to 100
|
2020-11-30 09:52:47 -05:00
|
|
|
endif
|
2023-02-15 17:27:51 -05:00
|
|
|
|
|
|
|
if(ncontest.eq.1 .and. lagain .and. iand(ndepth,16).eq.16) go to 50
|
|
|
|
if(ncontest.eq.1 .and. lagain .and. iand(ndepth,16).eq.0) go to 100
|
2021-01-08 09:42:07 -05:00
|
|
|
|
2021-02-01 10:54:04 -05:00
|
|
|
! Prepare for a single-period decode with iaptype = 0, 1, 2, or 4
|
2020-12-28 15:27:10 -05:00
|
|
|
jpk0=(xdt+1.0)*6000 !Index of nominal start of signal
|
|
|
|
if(ntrperiod.le.30) jpk0=(xdt+0.5)*6000 !For shortest sequences
|
2020-10-30 11:07:44 -04:00
|
|
|
if(jpk0.lt.0) jpk0=0
|
2021-02-01 13:28:59 -05:00
|
|
|
call ana64(iwave,npts,c00) !Convert to complex c00() at 6000 Sa/s
|
2020-10-30 11:07:44 -04:00
|
|
|
if(lapcqonly) npasses=1
|
2020-11-11 15:06:24 -05:00
|
|
|
iaptype=0
|
2021-01-14 14:56:37 -05:00
|
|
|
do ipass=0,npasses !Loop over AP passes
|
2020-12-28 15:27:10 -05:00
|
|
|
apmask=0 !Try first with no AP information
|
2020-10-30 11:07:44 -04:00
|
|
|
apsymbols=0
|
|
|
|
if(ipass.ge.1) then
|
2020-12-28 15:27:10 -05:00
|
|
|
! Subsequent passes use AP information appropiate for nQSOprogress
|
2020-11-11 15:06:24 -05:00
|
|
|
call q65_ap(nQSOprogress,ipass,ncontest,lapcqonly,iaptype, &
|
|
|
|
apsym0,apmask1,apsymbols1)
|
2020-10-30 11:07:44 -04:00
|
|
|
write(c78,1050) apmask1
|
|
|
|
1050 format(78i1)
|
|
|
|
read(c78,1060) apmask
|
|
|
|
1060 format(13b6.6)
|
|
|
|
write(c78,1050) apsymbols1
|
|
|
|
read(c78,1060) apsymbols
|
|
|
|
endif
|
2020-12-28 15:27:10 -05:00
|
|
|
|
2023-02-10 10:37:27 -05:00
|
|
|
call timer('q65loop1',0)
|
2021-01-13 11:21:59 -05:00
|
|
|
call q65_loops(c00,npts/2,nsps/2,nsubmode,ndepth,jpk0, &
|
2020-12-30 15:05:02 -05:00
|
|
|
xdt,f0,iaptype,xdt1,f1,snr2,dat4,idec)
|
2023-02-10 10:37:27 -05:00
|
|
|
call timer('q65loop1',1)
|
2021-01-19 14:11:21 -05:00
|
|
|
if(idec.ge.0) then
|
|
|
|
dtdec=xdt1
|
|
|
|
f0dec=f1
|
|
|
|
go to 100 !Successful decode, we're done
|
|
|
|
endif
|
2021-01-14 15:52:51 -05:00
|
|
|
enddo ! ipass
|
2020-10-30 11:07:44 -04:00
|
|
|
|
2021-01-19 16:06:10 -05:00
|
|
|
if(iand(ndepth,16).eq.0 .or. navg(iseq).lt.2) go to 100
|
2021-03-16 11:39:59 -04:00
|
|
|
|
2021-01-14 15:19:33 -05:00
|
|
|
! There was no single-transmission decode. Try for an average 'q3n' decode.
|
2023-02-15 13:52:01 -05:00
|
|
|
50 iavg=1
|
|
|
|
call timer('list_avg',0)
|
2021-01-14 15:52:51 -05:00
|
|
|
! Call top-level routine in q65 module: establish sync and try for a q3
|
|
|
|
! decode, this time using the cumulative 's1a' symbol spectra.
|
2023-01-23 19:22:34 -05:00
|
|
|
call q65_dec0(iavg,iwave,ntrperiod,nfqso,ntol,lclearave, &
|
2021-10-11 14:56:08 -04:00
|
|
|
emedelay,xdt,f0,snr1,width,dat4,snr2,idec,stageno)
|
2021-01-15 12:40:38 -05:00
|
|
|
call timer('list_avg',1)
|
2021-06-25 14:57:36 -04:00
|
|
|
|
2021-01-15 12:40:38 -05:00
|
|
|
if(idec.ge.0) then
|
2021-01-19 14:11:21 -05:00
|
|
|
dtdec=xdt !We have a list-decode result from averaged data
|
|
|
|
f0dec=f0
|
2021-01-19 16:06:10 -05:00
|
|
|
nused=navg(iseq)
|
2021-01-15 12:40:38 -05:00
|
|
|
go to 100
|
|
|
|
endif
|
2021-01-14 15:19:33 -05:00
|
|
|
|
2021-02-01 10:54:04 -05:00
|
|
|
! There was no 'q3n' decode. Try for a 'q[0124]n' decode.
|
2021-01-15 12:40:38 -05:00
|
|
|
! Call top-level routine in q65 module: establish sync and try for a q[012]n
|
|
|
|
! decode, this time using the cumulative 's1a' symbol spectra.
|
|
|
|
|
|
|
|
call timer('q65_avg ',0)
|
|
|
|
iavg=2
|
2023-01-23 19:22:34 -05:00
|
|
|
call q65_dec0(iavg,iwave,ntrperiod,nfqso,ntol,lclearave, &
|
2021-10-11 14:56:08 -04:00
|
|
|
emedelay,xdt,f0,snr1,width,dat4,snr2,idec,stageno)
|
2021-01-15 12:40:38 -05:00
|
|
|
call timer('q65_avg ',1)
|
2021-01-19 14:11:21 -05:00
|
|
|
if(idec.ge.0) then
|
|
|
|
dtdec=xdt !We have a q[012]n result
|
|
|
|
f0dec=f0
|
2021-01-19 16:06:10 -05:00
|
|
|
nused=navg(iseq)
|
2021-01-19 14:11:21 -05:00
|
|
|
endif
|
2021-01-15 12:40:38 -05:00
|
|
|
|
2021-10-22 10:22:23 -04:00
|
|
|
100 if(idec.lt.0 .and. max_drift.eq.50) then
|
|
|
|
stageno = 5
|
2021-10-11 14:56:08 -04:00
|
|
|
call timer('q65_dec0',0)
|
|
|
|
! Call top-level routine in q65 module: establish sync and try for a
|
|
|
|
! q3 or q0 decode.
|
2023-01-23 19:22:34 -05:00
|
|
|
call q65_dec0(iavg,iwave,ntrperiod,nfqso,ntol,lclearave, &
|
2021-10-11 14:56:08 -04:00
|
|
|
emedelay,xdt,f0,snr1,width,dat4,snr2,idec,stageno)
|
|
|
|
call timer('q65_dec0',1)
|
|
|
|
if(idec.ge.0) then
|
|
|
|
dtdec=xdt !We have a q[012]n result
|
|
|
|
f0dec=f0
|
|
|
|
endif
|
|
|
|
endif ! if(idec.lt.0)
|
|
|
|
|
|
|
|
decoded=' '
|
2021-01-14 13:13:40 -05:00
|
|
|
if(idec.ge.0) then
|
2020-12-30 10:42:27 -05:00
|
|
|
! idec Meaning
|
|
|
|
! ------------------------------------------------------
|
|
|
|
! -1: No decode
|
2021-01-14 14:56:37 -05:00
|
|
|
! 0: Decode without AP information
|
|
|
|
! 1: Decode with AP for "CQ ? ?"
|
|
|
|
! 2: Decode with AP for "MyCall ? ?"
|
|
|
|
! 3: Decode with AP for "MyCall DxCall ?"
|
2020-12-30 10:42:27 -05:00
|
|
|
|
2020-12-28 15:27:10 -05:00
|
|
|
! Unpack decoded message for display to user
|
2020-11-11 15:06:24 -05:00
|
|
|
write(c77,1000) dat4(1:12),dat4(13)/2
|
2020-10-27 13:08:07 -04:00
|
|
|
1000 format(12b6.6,b5.5)
|
2021-11-02 15:17:51 -04:00
|
|
|
call unpack77(c77,1,decoded,unpk77_success) !Unpack to get decoded
|
|
|
|
idupe=0
|
|
|
|
do i=1,ndecodes
|
|
|
|
if(decodes(i).eq.decoded) idupe=1
|
|
|
|
enddo
|
|
|
|
if(idupe.eq.0) then
|
|
|
|
ndecodes=min(ndecodes+1,100)
|
|
|
|
decodes(ndecodes)=decoded
|
2023-01-04 12:02:10 -05:00
|
|
|
f0decodes(ndecodes)=f0dec
|
2023-02-12 17:33:21 -05:00
|
|
|
xdtdecodes(ndecodes)=dtdec
|
2023-01-24 08:17:42 -05:00
|
|
|
call q65_snr(dat4,dtdec,f0dec,mode_q65,snr2)
|
2021-11-02 15:17:51 -04:00
|
|
|
nsnr=nint(snr2)
|
|
|
|
call this%callback(nutc,snr1,nsnr,dtdec,f0dec,decoded, &
|
|
|
|
idec,nused,ntrperiod)
|
2023-02-07 15:17:09 -05:00
|
|
|
if(ncontest.eq.1) then
|
2023-02-16 16:50:24 -05:00
|
|
|
call q65_hist2(nint(f0dec),decoded,callers,nhist2)
|
2023-02-07 15:17:09 -05:00
|
|
|
else
|
|
|
|
call q65_hist(nint(f0dec),msg0=decoded)
|
|
|
|
endif
|
2021-11-02 15:17:51 -04:00
|
|
|
if(iand(ndepth,128).ne.0 .and. .not.lagain .and. &
|
|
|
|
int(abs(f0dec-nfqso)).le.ntol ) call q65_clravg !AutoClrAvg
|
|
|
|
call sec0(1,tdecode)
|
2023-01-17 10:20:56 -05:00
|
|
|
open(22,file=trim(data_dir)//'/q65_decodes.txt',status='unknown', &
|
|
|
|
position='append',iostat=ios)
|
2021-11-02 15:17:51 -04:00
|
|
|
if(ios.eq.0) then
|
2021-01-28 13:01:52 -05:00
|
|
|
! Save decoding parameters to q65_decoded.dat, for later analysis.
|
2021-11-02 15:17:51 -04:00
|
|
|
write(cmode,'(i3)') ntrperiod
|
|
|
|
cmode(4:4)=char(ichar('A')+nsubmode)
|
|
|
|
c6=hiscall(1:6)
|
|
|
|
if(c6.eq.' ') c6='<b> '
|
|
|
|
c4=hisgrid(1:4)
|
|
|
|
if(c4.eq.' ') c4='<b> '
|
2023-02-10 13:09:47 -05:00
|
|
|
fmt='(i6.4,1x,a4,i5,4i2,8i3,i4,f6.2,f7.1,f6.1,f7.1,f6.2,'// &
|
2021-11-02 15:17:51 -04:00
|
|
|
'1x,a6,1x,a6,1x,a4,1x,a)'
|
|
|
|
if(ntrperiod.le.30) fmt(5:5)='6'
|
|
|
|
if(idec.eq.3) nrc=0
|
2023-01-17 10:20:56 -05:00
|
|
|
write(22,fmt) nutc,cmode,nfqso,nQSOprogress,idec,idfbest,idtbest, &
|
2023-02-10 13:09:47 -05:00
|
|
|
ibwa,ibwb,ibw,ndistbest,nused,icand,ncand,nrc,ndepth,xdt, &
|
|
|
|
f0,snr2,plog,tdecode,mycall(1:6),c6,c4,trim(decoded)
|
2023-01-17 10:20:56 -05:00
|
|
|
close(22)
|
2021-11-02 15:17:51 -04:00
|
|
|
endif
|
2021-01-28 13:01:52 -05:00
|
|
|
endif
|
2020-08-01 09:24:59 -04:00
|
|
|
endif
|
2021-01-19 16:06:10 -05:00
|
|
|
navg0=1000*navg(0) + navg(1)
|
2021-02-02 09:58:04 -05:00
|
|
|
if(single_decode .or. lagain) go to 900
|
2020-08-01 15:12:37 -04:00
|
|
|
|
2021-02-01 13:28:59 -05:00
|
|
|
do icand=1,ncand
|
|
|
|
! Prepare for single-period candidate decodes with iaptype = 0, 1, 2, or 4
|
|
|
|
snr1=candidates(icand,1)
|
|
|
|
xdt= candidates(icand,2)
|
|
|
|
f0 = candidates(icand,3)
|
2023-01-04 12:02:10 -05:00
|
|
|
do i=1,ndecodes
|
|
|
|
fdiff=f0-f0decodes(i)
|
|
|
|
if(fdiff.gt.-baud*mode_q65 .and. fdiff.lt.65*baud*mode_q65) go to 800
|
|
|
|
enddo
|
2023-02-12 17:33:21 -05:00
|
|
|
|
|
|
|
!### TEST REGION
|
|
|
|
if(ncontest.eq.-1) then
|
|
|
|
call timer('q65_dec0',0)
|
|
|
|
! Call top-level routine in q65 module: establish sync and try for a
|
|
|
|
! q3 or q0 decode.
|
|
|
|
call q65_dec0(iavg,iwave,ntrperiod,nint(f0),ntol,lclearave, &
|
|
|
|
emedelay,xdt,f0,snr1,width,dat4,snr2,idec,stageno)
|
|
|
|
call timer('q65_dec0',1)
|
|
|
|
if(idec.ge.0) then
|
|
|
|
dtdec=xdt !We have a q3 or q0 decode at f0
|
|
|
|
f0dec=f0
|
|
|
|
go to 200
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
!###
|
2021-02-01 13:28:59 -05:00
|
|
|
jpk0=(xdt+1.0)*6000 !Index of nominal start of signal
|
|
|
|
if(ntrperiod.le.30) jpk0=(xdt+0.5)*6000 !For shortest sequences
|
|
|
|
if(jpk0.lt.0) jpk0=0
|
|
|
|
call ana64(iwave,npts,c00) !Convert to complex c00() at 6000 Sa/s
|
|
|
|
call ft8apset(mycall,hiscall,ncontest,apsym0,aph10) ! Generate ap symbols
|
|
|
|
where(apsym0.eq.-1) apsym0=0
|
|
|
|
|
|
|
|
npasses=2
|
|
|
|
if(nQSOprogress.eq.5) npasses=3
|
|
|
|
if(lapcqonly) npasses=1
|
|
|
|
iaptype=0
|
|
|
|
do ipass=0,npasses !Loop over AP passes
|
2023-02-10 10:37:27 -05:00
|
|
|
! write(*,3001) nutc,icand,ipass,f0,xdt,snr1
|
|
|
|
!3001 format('a',i5.4,2i3,3f7.1)
|
2021-02-01 13:28:59 -05:00
|
|
|
apmask=0 !Try first with no AP information
|
|
|
|
apsymbols=0
|
|
|
|
if(ipass.ge.1) then
|
|
|
|
! Subsequent passes use AP information appropiate for nQSOprogress
|
|
|
|
call q65_ap(nQSOprogress,ipass,ncontest,lapcqonly,iaptype, &
|
|
|
|
apsym0,apmask1,apsymbols1)
|
|
|
|
write(c78,1050) apmask1
|
|
|
|
read(c78,1060) apmask
|
|
|
|
write(c78,1050) apsymbols1
|
|
|
|
read(c78,1060) apsymbols
|
|
|
|
endif
|
|
|
|
|
2023-02-10 10:37:27 -05:00
|
|
|
call timer('q65loop2',0)
|
2021-02-01 13:28:59 -05:00
|
|
|
call q65_loops(c00,npts/2,nsps/2,nsubmode,ndepth,jpk0, &
|
|
|
|
xdt,f0,iaptype,xdt1,f1,snr2,dat4,idec)
|
2023-02-10 10:37:27 -05:00
|
|
|
call timer('q65loop2',1)
|
2021-11-02 15:17:51 -04:00
|
|
|
! write(*,3001) '=e',nfqso,ntol,ndepth,xdt,f0,idec
|
2021-02-01 13:28:59 -05:00
|
|
|
if(idec.ge.0) then
|
|
|
|
dtdec=xdt1
|
|
|
|
f0dec=f1
|
|
|
|
go to 200 !Successful decode, we're done
|
|
|
|
endif
|
|
|
|
enddo ! ipass
|
|
|
|
|
|
|
|
200 decoded=' '
|
|
|
|
if(idec.ge.0) then
|
|
|
|
! Unpack decoded message for display to user
|
|
|
|
write(c77,1000) dat4(1:12),dat4(13)/2
|
2021-11-02 15:17:51 -04:00
|
|
|
call unpack77(c77,1,decoded,unpk77_success) !Unpack to get decoded
|
|
|
|
idupe=0
|
|
|
|
do i=1,ndecodes
|
|
|
|
if(decodes(i).eq.decoded) idupe=1
|
|
|
|
enddo
|
|
|
|
if(idupe.eq.0) then
|
|
|
|
ndecodes=min(ndecodes+1,100)
|
|
|
|
decodes(ndecodes)=decoded
|
2023-01-04 12:02:10 -05:00
|
|
|
f0decodes(ndecodes)=f0dec
|
2023-01-24 08:17:42 -05:00
|
|
|
call q65_snr(dat4,dtdec,f0dec,mode_q65,snr2)
|
2021-11-02 15:17:51 -04:00
|
|
|
nsnr=nint(snr2)
|
|
|
|
call this%callback(nutc,snr1,nsnr,dtdec,f0dec,decoded, &
|
|
|
|
idec,nused,ntrperiod)
|
2023-02-07 15:17:09 -05:00
|
|
|
if(ncontest.eq.1) then
|
2023-02-16 16:50:24 -05:00
|
|
|
call q65_hist2(nint(f0dec),decoded,callers,nhist2)
|
2023-02-07 15:17:09 -05:00
|
|
|
else
|
|
|
|
call q65_hist(nint(f0dec),msg0=decoded)
|
|
|
|
endif
|
2021-11-02 15:17:51 -04:00
|
|
|
if(iand(ndepth,128).ne.0 .and. .not.lagain .and. &
|
|
|
|
int(abs(f0dec-nfqso)).le.ntol ) call q65_clravg !AutoClrAvg
|
|
|
|
call sec0(1,tdecode)
|
2023-01-04 12:02:10 -05:00
|
|
|
ios=1
|
2023-01-17 10:20:56 -05:00
|
|
|
open(22,file=trim(data_dir)//'/q65_decodes.txt',status='unknown',&
|
|
|
|
position='append',iostat=ios)
|
2021-11-02 15:17:51 -04:00
|
|
|
if(ios.eq.0) then
|
2021-02-01 13:28:59 -05:00
|
|
|
! Save decoding parameters to q65_decoded.dat, for later analysis.
|
2021-11-02 15:17:51 -04:00
|
|
|
write(cmode,'(i3)') ntrperiod
|
|
|
|
cmode(4:4)=char(ichar('A')+nsubmode)
|
|
|
|
c6=hiscall(1:6)
|
|
|
|
if(c6.eq.' ') c6='<b> '
|
|
|
|
c4=hisgrid(1:4)
|
|
|
|
if(c4.eq.' ') c4='<b> '
|
2023-02-10 13:09:47 -05:00
|
|
|
fmt='(i6.4,1x,a4,i5,4i2,8i3,i4,f6.2,f7.1,f6.1,f7.1,f6.2,'// &
|
2021-11-02 15:17:51 -04:00
|
|
|
'1x,a6,1x,a6,1x,a4,1x,a)'
|
|
|
|
if(ntrperiod.le.30) fmt(5:5)='6'
|
|
|
|
if(idec.eq.3) nrc=0
|
2023-01-17 10:20:56 -05:00
|
|
|
write(22,fmt) nutc,cmode,nfqso,nQSOprogress,idec,idfbest, &
|
2023-02-10 13:09:47 -05:00
|
|
|
idtbest,ibwa,ibwb,ibw,ndistbest,nused,icand,ncand,nrc, &
|
|
|
|
ndepth,xdt,f0,snr2,plog,tdecode,mycall(1:6),c6,c4, &
|
|
|
|
trim(decoded)
|
2023-01-17 10:20:56 -05:00
|
|
|
close(22)
|
2021-11-02 15:17:51 -04:00
|
|
|
endif
|
2021-02-01 13:28:59 -05:00
|
|
|
endif
|
|
|
|
endif
|
2023-01-04 12:02:10 -05:00
|
|
|
800 continue
|
2021-03-16 11:39:59 -04:00
|
|
|
enddo ! icand
|
2021-04-02 09:56:50 -04:00
|
|
|
if(iavg.eq.0 .and.navg(iseq).ge.2 .and. iand(ndepth,16).ne.0) go to 50
|
2023-02-12 17:33:21 -05:00
|
|
|
|
2023-02-16 16:50:24 -05:00
|
|
|
900 if(ncontest.ne.1 .or. lagain) go to 999
|
2023-02-12 17:33:21 -05:00
|
|
|
if(ntrperiod.ne.60 .or. nsubmode.ne.0) go to 999
|
|
|
|
|
|
|
|
! This is first time here, and we're running Q65-60A in NA VHF Contest mode.
|
|
|
|
! Return a list of potential sync frequencies at which to try q3 decoding.
|
|
|
|
|
|
|
|
k=0
|
|
|
|
nqf=0
|
|
|
|
bw=baud*mode_q65*65
|
|
|
|
do i=1,ncand
|
|
|
|
! snr1=candidates(i,1)
|
|
|
|
! xdt= candidates(i,2)
|
|
|
|
f0 = candidates(i,3)
|
|
|
|
do j=1,ndecodes ! Already decoded one at or near this frequency?
|
|
|
|
fj=f0decodes(j)
|
|
|
|
if(f0.gt.fj-5.0 .and. f0.lt.fj+bw+5.0) go to 990
|
|
|
|
enddo
|
|
|
|
k=k+1
|
|
|
|
nqf(k)=nint(f0)
|
|
|
|
990 continue
|
|
|
|
enddo
|
|
|
|
|
|
|
|
999 return
|
2020-08-01 09:24:59 -04:00
|
|
|
end subroutine decode
|
|
|
|
|
2020-10-25 13:58:18 -04:00
|
|
|
end module q65_decode
|