WSJT-X/lib/q65_decode.f90

167 lines
5.3 KiB
Fortran
Raw Normal View History

module q65_decode
2020-08-01 09:24:59 -04:00
type :: q65_decoder
procedure(q65_decode_callback), pointer :: callback
2020-08-01 09:24:59 -04:00
contains
procedure :: decode
end type q65_decoder
2020-08-01 09:24:59 -04:00
abstract interface
subroutine q65_decode_callback (this,nutc,sync,nsnr,dt,freq, &
2020-08-01 09:24:59 -04:00
decoded,nap,qual,ntrperiod,fmid,w50)
import q65_decoder
2020-08-01 09:24:59 -04:00
implicit none
class(q65_decoder), intent(inout) :: this
2020-08-01 09:24:59 -04:00
integer, intent(in) :: nutc
real, intent(in) :: sync
integer, intent(in) :: nsnr
real, intent(in) :: dt
real, intent(in) :: freq
character(len=37), intent(in) :: decoded
integer, intent(in) :: nap
real, intent(in) :: qual
integer, intent(in) :: ntrperiod
real, intent(in) :: fmid
real, intent(in) :: w50
end subroutine q65_decode_callback
2020-08-01 09:24:59 -04:00
end interface
contains
subroutine decode(this,callback,iwave,nutc,ntrperiod,nsubmode,nfqso, &
ntol,ndepth,mycall,hiscall,hisgrid,nQSOprogress,ncontest,lapcqonly)
2020-08-01 09:24:59 -04:00
! Decodes 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)
! ndepth Optional decoding level
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
use packjt77
2020-08-01 09:24:59 -04:00
use, intrinsic :: iso_c_binding
2020-10-09 13:16:25 -04:00
parameter (NMAX=300*12000) !Max TRperiod is 300 s
class(q65_decoder), intent(inout) :: this
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
character*77 c77
character*78 c78
integer*2 iwave(NMAX) !Raw data
2020-10-17 13:16:46 -04:00
real, allocatable :: dd(:) !Raw data
integer dat4(13) !Decoded message as 12 6-bit integers
integer apsym0(58),aph10(10)
integer apmask1(78),apsymbols1(78)
integer apmask(13),apsymbols(13)
logical lapcqonly,unpk77_success
2020-10-09 13:16:25 -04:00
complex, allocatable :: c00(:) !Analytic signal, 6000 Sa/s
complex, allocatable :: c0(:) !Analytic signal, 6000 Sa/s
mode65=2**nsubmode
nfft1=ntrperiod*12000
nfft2=ntrperiod*6000
2020-10-17 13:16:46 -04:00
allocate(dd(NMAX))
allocate (c00(0:nfft1-1))
allocate (c0(0:nfft1-1))
if(ntrperiod.eq.15) then
nsps=1800
else if(ntrperiod.eq.30) then
nsps=3600
else if(ntrperiod.eq.60) then
nsps=7200
else if(ntrperiod.eq.120) then
nsps=16000
else if(ntrperiod.eq.300) then
nsps=41472
else
2020-10-09 14:12:34 -04:00
stop 'Invalid TR period'
endif
npts=ntrperiod*12000
baud=12000.0/nsps
df1=12000.0/nfft1
this%callback => callback
2020-10-09 14:12:34 -04:00
if(nutc.eq.-999) print*,lapdx,nfa,nfb,nfqso !Silence warning
nFadingModel=1
! call qra_params(ndepth,maxaptype,idfmax,idtmax,ibwmin,ibwmax,maxdist)
2020-10-09 14:12:34 -04:00
call timer('sync_q65',0)
2020-11-02 15:59:10 -05:00
call sync_q65(iwave,ntrperiod*12000,mode65,nsps,nfqso,ntol,xdt,f0, &
snr1,width)
2020-10-09 14:12:34 -04:00
call timer('sync_q65',1)
2020-10-19 15:24:32 -04:00
irc=-1
if(snr1.lt.2.8) go to 100
2020-11-02 15:59:10 -05:00
jpk0=(xdt+1.0)*6000 !### Is this OK?
if(ntrperiod.le.30) jpk0=(xdt+0.5)*6000 !###
if(jpk0.lt.0) jpk0=0
fac=1.0/32767.0
dd=fac*iwave
nmode=65
call ana64(dd,npts,c00)
call ft8apset(mycall,hiscall,ncontest,apsym0,aph10)
where(apsym0.eq.-1) apsym0=0
npasses=2
if(nQSOprogress.eq.3 .or.nQSOprogress.eq.4) npasses=4
if(nQSOprogress.eq.5) npasses=3
if(lapcqonly) npasses=1
iaptype=0
do ipass=0,npasses
! write(54,3000) nQSOprogress,ipass
!3000 format(i1,i2)
apmask=0
apsymbols=0
if(ipass.ge.1) then
call q65_ap(nQSOprogress,ipass,ncontest,lapcqonly,iaptype, &
apsym0,apmask1,apsymbols1)
write(c78,1050) apmask1
1050 format(78i1)
read(c78,1060) apmask
1060 format(13b6.6)
write(c78,1050) apsymbols1
read(c78,1060) apsymbols
! write(54,3001) iaptype,c78
!3001 format('a',i2,1x,a78)
endif
! write(54,3002) apmask,apsymbols
!3002 format('b ',13b6.6/4x,13b6.6)
call timer('q65loops',0)
call q65_loops(c00,npts/2,nsps/2,nmode,mode65,nsubmode,nFadingModel, &
ndepth,jpk0,xdt,f0,width,iaptype,apmask,apsymbols,snr1,xdt1,f1, &
snr2,irc,dat4)
call timer('q65loops',1)
2020-10-19 15:24:32 -04:00
snr2=snr2 + db(6912.0/nsps)
if(irc.ge.0) exit
enddo
100 decoded=' '
2020-08-01 09:24:59 -04:00
if(irc.ge.0) then
2020-11-02 15:59:10 -05:00
!###
navg=irc/100
! irc=100*navg + ipass
irc=100*navg + iaptype
!###
write(c77,1000) dat4(1:12),dat4(13)/2
1000 format(12b6.6,b5.5)
call unpack77(c77,0,decoded,unpk77_success) !Unpack to get msgsent
2020-08-01 09:24:59 -04:00
nsnr=nint(snr2)
call this%callback(nutc,sync,nsnr,xdt1,f1,decoded, &
irc,qual,ntrperiod,fmid,w50)
2020-08-01 09:24:59 -04:00
else
2020-11-02 15:59:10 -05:00
! Report sync, even if no decode.
nsnr=db(snr1) - 35.0
call this%callback(nutc,sync,nsnr,xdt1,f1,decoded, &
irc,qual,ntrperiod,fmid,w50)
2020-08-01 09:24:59 -04:00
endif
2020-08-01 09:24:59 -04:00
return
end subroutine decode
end module q65_decode