Move more into q65 module.

This commit is contained in:
Joe Taylor 2021-01-13 10:55:01 -05:00
parent dc4c3e87eb
commit 201004a47d
4 changed files with 16 additions and 17 deletions

View File

@ -758,14 +758,14 @@ contains
return
end subroutine fst4_decoded
subroutine q65_decoded (this,nutc,sync,nsnr,dt,freq,decoded,idec,ntrperiod)
subroutine q65_decoded (this,nutc,snr1,nsnr,dt,freq,decoded,idec,ntrperiod)
use q65_decode
implicit none
class(q65_decoder), intent(inout) :: this
integer, intent(in) :: nutc
real, intent(in) :: sync
real, intent(in) :: snr1
integer, intent(in) :: nsnr
real, intent(in) :: dt
real, intent(in) :: freq
@ -796,12 +796,12 @@ contains
if(ntrperiod.lt.60) then
write(*,1001) nutc,nsnr,dt,nint(freq),decoded,cflags
1001 format(i6.6,i4,f5.1,i5,' : ',1x,a37,1x,a3)
write(13,1002) nutc,nint(sync),nsnr,dt,freq,0,decoded
write(13,1002) nutc,nint(snr1),nsnr,dt,freq,0,decoded
1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a37,' Q65')
else
write(*,1003) nutc,nsnr,dt,nint(freq),decoded,cflags
1003 format(i4.4,i4,f5.1,i5,' : ',1x,a37,1x,a3)
write(13,1004) nutc,nint(sync),nsnr,dt,freq,0,decoded
write(13,1004) nutc,nint(snr1),nsnr,dt,freq,0,decoded
1004 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a37,' Q65')
endif

View File

@ -7,13 +7,13 @@ module q65_decode
end type q65_decoder
abstract interface
subroutine q65_decode_callback (this,nutc,sync,nsnr,dt,freq, &
subroutine q65_decode_callback (this,nutc,snr1,nsnr,dt,freq, &
decoded,nap,ntrperiod)
import q65_decoder
implicit none
class(q65_decoder), intent(inout) :: this
integer, intent(in) :: nutc
real, intent(in) :: sync
real, intent(in) :: snr1
integer, intent(in) :: nsnr
real, intent(in) :: dt
real, intent(in) :: freq
@ -185,13 +185,13 @@ contains
1000 format(12b6.6,b5.5)
call unpack77(c77,0,decoded,unpk77_success) !Unpack to get msgsent
nsnr=nint(snr2)
call this%callback(nutc,sync,nsnr,xdt1,f1,decoded,idec,ntrperiod)
call this%callback(nutc,snr1,nsnr,xdt1,f1,decoded,idec,ntrperiod)
call q65_clravg
else
! Report sync, even if no decode.
! Report snr1, even if no decode.
nsnr=db(snr1) - 35.0
idec=-1
call this%callback(nutc,sync,nsnr,xdt1,f1,decoded, &
call this%callback(nutc,snr1,nsnr,xdt1,f1,decoded, &
idec,ntrperiod)
endif

View File

@ -11,6 +11,7 @@ module q65
integer codewords(63,206)
integer navg,ibwa,ibwb,ncw
real,allocatable,save :: s1a(:,:) !Cumulative symbol spectra
real sync(85) !sync vector
contains

View File

@ -22,15 +22,14 @@ subroutine q65_sync(nutc,iwave,ntrperiod,mode_q65,nsps, &
integer dat4(13)
integer ijpk(2)
character*37 decoded
logical lclearave
logical first,lclearave
real, allocatable :: s1(:,:) !Symbol spectra, 1/8-symbol steps
real, allocatable :: s3(:,:) !Data-symbol energies s3(LL,63)
real, allocatable :: ccf(:,:) !CCF(freq,lag)
real, allocatable :: ccf1(:) !CCF(freq) at best lag
real, allocatable :: ccf2(:) !CCF(freq) at any lag
real sync(85) !sync vector
data sync(1)/99.0/
save sync
data first/.true./
save first
if(nutc+ndepth.eq.-999) stop
irc=-2
@ -65,7 +64,7 @@ subroutine q65_sync(nutc,iwave,ntrperiod,mode_q65,nsps, &
endif
s3=0.
if(sync(1).eq.99.0) then !Generate the sync vector
if(first) then !Generate the sync vector
sync=-22.0/63.0 !Sync tone OFF
do k=1,22
sync(isync(k))=1.0 !Sync tone ON
@ -102,7 +101,7 @@ subroutine q65_sync(nutc,iwave,ntrperiod,mode_q65,nsps, &
if(ncw.gt.0) then
! Try list decoding via "Deep Likelihood".
call timer('list_dec',0)
call q65_dec_q3(sync,df,s1,iz,jz,ia, &
call q65_dec_q3(df,s1,iz,jz,ia, &
nsps,mode_q65,lag1,lag2,i0,j0,ccf,ccf1,ccf2,ia2,s3,LL,snr2, &
dat4,idec,decoded)
call timer('list_dec',1)
@ -215,7 +214,7 @@ subroutine q65_symspec(iwave,nmax,nsps,iz,jz,istep,nsmo,s1)
return
end subroutine q65_symspec
subroutine q65_dec_q3(sync,df,s1,iz,jz,ia, &
subroutine q65_dec_q3(df,s1,iz,jz,ia, &
nsps,mode_q65,lag1,lag2,i0,j0,ccf,ccf1,ccf2,ia2,s3,LL,snr2, &
dat4,idec,decoded)
@ -229,7 +228,6 @@ subroutine q65_dec_q3(sync,df,s1,iz,jz,ia, &
real ccf2(-ia2:ia2)
real s1(iz,jz)
real s3(-64:LL-65,63)
real sync(85) !sync vector
ipk=0
jpk=0