Mostly(?) changed QRA66 to QRA65 on the Fortran side.

This commit is contained in:
Joe Taylor 2020-09-25 12:21:57 -04:00
parent 2057600f43
commit 6ebc700288
7 changed files with 59 additions and 63 deletions

View File

@ -380,7 +380,7 @@ set (wsjt_FSRCS
lib/options.f90 lib/options.f90
lib/packjt.f90 lib/packjt.f90
lib/77bit/packjt77.f90 lib/77bit/packjt77.f90
lib/qra66_decode.f90 lib/qra65_decode.f90
lib/readwav.f90 lib/readwav.f90
lib/timer_C_wrapper.f90 lib/timer_C_wrapper.f90
lib/timer_impl.f90 lib/timer_impl.f90
@ -568,7 +568,7 @@ set (wsjt_FSRCS
lib/softsym9w.f90 lib/softsym9w.f90
lib/shell.f90 lib/shell.f90
lib/spec64.f90 lib/spec64.f90
lib/spec66.f90 lib/spec_qra65.f90
lib/spec9f.f90 lib/spec9f.f90
lib/stdmsg.f90 lib/stdmsg.f90
lib/subtract65.f90 lib/subtract65.f90
@ -580,8 +580,8 @@ set (wsjt_FSRCS
lib/symspec65.f90 lib/symspec65.f90
lib/sync4.f90 lib/sync4.f90
lib/sync64.f90 lib/sync64.f90
lib/sync66.f90
lib/sync65.f90 lib/sync65.f90
lib/sync_qra65.f90
lib/ft4/getcandidates4.f90 lib/ft4/getcandidates4.f90
lib/ft4/get_ft4_bitmetrics.f90 lib/ft4/get_ft4_bitmetrics.f90
lib/ft8/sync8.f90 lib/ft8/sync8.f90
@ -1335,11 +1335,8 @@ target_link_libraries (sumsim wsjt_fort wsjt_cxx)
add_executable (qra64sim lib/qra/qra64/qra64sim.f90 wsjtx.rc) add_executable (qra64sim lib/qra/qra64/qra64sim.f90 wsjtx.rc)
target_link_libraries (qra64sim wsjt_fort wsjt_cxx) target_link_libraries (qra64sim wsjt_fort wsjt_cxx)
add_executable (qra66sim lib/qra/qra66/qra66sim.f90 wsjtx.rc) add_executable (qra65sim lib/qra/qra65/qra65sim.f90 wsjtx.rc)
target_link_libraries (qra66sim wsjt_fort wsjt_cxx) target_link_libraries (qra65sim wsjt_fort wsjt_cxx)
#add_executable (test_sync66 lib/test_sync66.f90 wsjtx.rc)
#target_link_libraries (test_sync66 wsjt_fort wsjt_cxx)
add_executable (jt49sim lib/jt49sim.f90 wsjtx.rc) add_executable (jt49sim lib/jt49sim.f90 wsjtx.rc)
target_link_libraries (jt49sim wsjt_fort wsjt_cxx) target_link_libraries (jt49sim wsjt_fort wsjt_cxx)
@ -1543,7 +1540,7 @@ install (TARGETS jt9 wsprd fmtave fcal fmeasure
if(WSJT_BUILD_UTILS) if(WSJT_BUILD_UTILS)
install (TARGETS ft8code jt65code qra64code qra64sim jt9code jt4code install (TARGETS ft8code jt65code qra64code qra64sim jt9code jt4code
msk144code fst4sim msk144code fst4sim qra65sim
RUNTIME DESTINATION ${CMAKE_INSTALL_BINDIR} COMPONENT runtime RUNTIME DESTINATION ${CMAKE_INSTALL_BINDIR} COMPONENT runtime
BUNDLE DESTINATION ${CMAKE_INSTALL_BINDIR} COMPONENT runtime BUNDLE DESTINATION ${CMAKE_INSTALL_BINDIR} COMPONENT runtime
) )

View File

@ -9,7 +9,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
use ft8_decode use ft8_decode
use ft4_decode use ft4_decode
use fst4_decode use fst4_decode
use qra66_decode use qra65_decode
include 'jt9com.f90' include 'jt9com.f90'
include 'timer_common.inc' include 'timer_common.inc'
@ -38,9 +38,9 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
integer :: decoded integer :: decoded
end type counting_fst4_decoder end type counting_fst4_decoder
type, extends(qra66_decoder) :: counting_qra66_decoder type, extends(qra65_decoder) :: counting_qra65_decoder
integer :: decoded integer :: decoded
end type counting_qra66_decoder end type counting_qra65_decoder
real ss(184,NSMAX) real ss(184,NSMAX)
logical baddata,newdat65,newdat9,single_decode,bVHF,bad0,newdat,ex logical baddata,newdat65,newdat9,single_decode,bVHF,bad0,newdat,ex
@ -59,7 +59,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
type(counting_ft8_decoder) :: my_ft8 type(counting_ft8_decoder) :: my_ft8
type(counting_ft4_decoder) :: my_ft4 type(counting_ft4_decoder) :: my_ft4
type(counting_fst4_decoder) :: my_fst4 type(counting_fst4_decoder) :: my_fst4
type(counting_qra66_decoder) :: my_qra66 type(counting_qra65_decoder) :: my_qra65
!cast C character arrays to Fortran character strings !cast C character arrays to Fortran character strings
datetime=transfer(params%datetime, datetime) datetime=transfer(params%datetime, datetime)
@ -75,7 +75,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
my_ft8%decoded = 0 my_ft8%decoded = 0
my_ft4%decoded = 0 my_ft4%decoded = 0
my_fst4%decoded = 0 my_fst4%decoded = 0
my_qra66%decoded = 0 my_qra65%decoded = 0
! For testing only: return Rx messages stored in a file as decodes ! For testing only: return Rx messages stored in a file as decodes
inquire(file='rx_messages.txt',exist=ex) inquire(file='rx_messages.txt',exist=ex)
@ -195,12 +195,12 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
endif endif
if(params%nmode.eq.66) then if(params%nmode.eq.66) then
! We're in QRA66 mode ! We're in QRA65 mode
call timer('decqra66',0) call timer('decqra65',0)
call my_qra66%decode(qra66_decoded,id2,params%nutc,params%ntr, & call my_qra65%decode(qra65_decoded,id2,params%nutc,params%ntr, &
params%nsubmode,params%nfqso,params%ntol,params%ndepth, & params%nsubmode,params%nfqso,params%ntol,params%ndepth, &
mycall,hiscall,hisgrid) mycall,hiscall,hisgrid)
call timer('decqra66',1) call timer('decqra65',1)
go to 800 go to 800
endif endif
@ -776,13 +776,13 @@ contains
return return
end subroutine fst4_decoded end subroutine fst4_decoded
subroutine qra66_decoded (this,nutc,sync,nsnr,dt,freq,decoded,irc, & subroutine qra65_decoded (this,nutc,sync,nsnr,dt,freq,decoded,irc, &
qual,ntrperiod,fmid,w50) qual,ntrperiod,fmid,w50)
use qra66_decode use qra65_decode
implicit none implicit none
class(qra66_decoder), intent(inout) :: this class(qra65_decoder), intent(inout) :: this
integer, intent(in) :: nutc integer, intent(in) :: nutc
real, intent(in) :: sync real, intent(in) :: sync
integer, intent(in) :: nsnr integer, intent(in) :: nsnr
@ -801,23 +801,23 @@ contains
write(*,1001) nutc,nsnr,dt,nint(freq),decoded,mod(irc,100),navg write(*,1001) nutc,nsnr,dt,nint(freq),decoded,mod(irc,100),navg
1001 format(i6.6,i4,f5.1,i5,' + ',1x,a37,1x,i2,i4) 1001 format(i6.6,i4,f5.1,i5,' + ',1x,a37,1x,i2,i4)
write(13,1002) nutc,nint(sync),nsnr,dt,freq,0,decoded write(13,1002) nutc,nint(sync),nsnr,dt,freq,0,decoded
1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a37,' QRA66') 1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a37,' QRA65')
else else
write(*,1003) nutc,nsnr,dt,nint(freq),decoded,mod(irc,100),navg write(*,1003) nutc,nsnr,dt,nint(freq),decoded,mod(irc,100),navg
1003 format(i4.4,i4,f5.1,i5,' + ',1x,a37,1x,i2,i4) 1003 format(i4.4,i4,f5.1,i5,' + ',1x,a37,1x,i2,i4)
write(13,1004) nutc,nint(sync),nsnr,dt,freq,0,decoded write(13,1004) nutc,nint(sync),nsnr,dt,freq,0,decoded
1004 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a37,' QRA66') 1004 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a37,' QRA65')
endif endif
call flush(6) call flush(6)
call flush(13) call flush(13)
select type(this) select type(this)
type is (counting_qra66_decoder) type is (counting_qra65_decoder)
this%decoded = this%decoded + 1 this%decoded = this%decoded + 1
end select end select
return return
end subroutine qra66_decoded end subroutine qra65_decoded
end subroutine multimode_decoder end subroutine multimode_decoder

View File

@ -16,7 +16,6 @@ subroutine genqra64(msg0,ichk,msgsent,itone,itype)
data isync/1,9,12,13,15,22,23,26,27,33,35,38,46,50,55,60,62,66,69,74,76,85/ data isync/1,9,12,13,15,22,23,26,27,33,35,38,46,50,55,60,62,66,69,74,76,85/
save save
print*,'ichk:',ichk
if(msg0(1:1).eq.'@') then if(msg0(1:1).eq.'@') then
read(msg0(2:5),*,end=1,err=1) nfreq read(msg0(2:5),*,end=1,err=1) nfreq
go to 2 go to 2

View File

@ -1,6 +1,6 @@
program qra66sim program qra65sim
! Generate simulated QRA66 data for testing the decoder. ! Generate simulated QRA65 data for testing the decoder.
use wavhdr use wavhdr
use packjt use packjt
@ -19,13 +19,13 @@ program qra66sim
nargs=iargc() nargs=iargc()
if(nargs.ne.8) then if(nargs.ne.8) then
print *, 'Usage: qra66sim "msg" A-E freq fDop DT TRp Nfiles SNR' print *, 'Usage: qra65sim "msg" A-E freq fDop DT TRp Nfiles SNR'
print *, 'Example: qra66sim "K1ABC W9XYZ EN37" A 1500 0.2 0.0 15 1 -10' print *, 'Example: qra65sim "K1ABC W9XYZ EN37" A 1500 0.2 0.0 15 1 -10'
go to 999 go to 999
endif endif
call getarg(1,msg) call getarg(1,msg)
call getarg(2,csubmode) call getarg(2,csubmode)
mode66=2**(ichar(csubmode)-ichar('A')) mode65=2**(ichar(csubmode)-ichar('A'))
call getarg(3,arg) call getarg(3,arg)
read(arg,*) f0 read(arg,*) f0
call getarg(4,arg) call getarg(4,arg)
@ -62,8 +62,7 @@ program qra66sim
dt=1.d0/fsample !Sample interval (s) dt=1.d0/fsample !Sample interval (s)
twopi=8.d0*atan(1.d0) twopi=8.d0*atan(1.d0)
nsym=85 !Number of channel symbols nsym=85 !Number of channel symbols
mode66=2**(ichar(csubmode) - ichar('A')) mode65=2**(ichar(csubmode) - ichar('A'))
print*,csubmode,mode66
ichk=65 !Flag sent to genqra64 ichk=65 !Flag sent to genqra64
call genqra64(msg,ichk,msgsent,itone,itype) call genqra64(msg,ichk,msgsent,itone,itype)
@ -108,7 +107,7 @@ program qra66sim
isym=i/nsps + 1 isym=i/nsps + 1
if(isym.gt.nsym) exit if(isym.gt.nsym) exit
if(isym.ne.isym0) then if(isym.ne.isym0) then
freq=f0 + itone(isym)*baud*mode66 freq=f0 + itone(isym)*baud*mode65
dphi=twopi*freq*dt dphi=twopi*freq*dt
isym0=isym isym0=isym
endif endif
@ -176,4 +175,4 @@ program qra66sim
! enddo ! enddo
enddo enddo
999 end program qra66sim 999 end program qra65sim

View File

@ -1,17 +1,17 @@
module qra66_decode module qra65_decode
type :: qra66_decoder type :: qra65_decoder
procedure(qra66_decode_callback), pointer :: callback procedure(qra65_decode_callback), pointer :: callback
contains contains
procedure :: decode procedure :: decode
end type qra66_decoder end type qra65_decoder
abstract interface abstract interface
subroutine qra66_decode_callback (this,nutc,sync,nsnr,dt,freq, & subroutine qra65_decode_callback (this,nutc,sync,nsnr,dt,freq, &
decoded,nap,qual,ntrperiod,fmid,w50) decoded,nap,qual,ntrperiod,fmid,w50)
import qra66_decoder import qra65_decoder
implicit none implicit none
class(qra66_decoder), intent(inout) :: this class(qra65_decoder), intent(inout) :: this
integer, intent(in) :: nutc integer, intent(in) :: nutc
real, intent(in) :: sync real, intent(in) :: sync
integer, intent(in) :: nsnr integer, intent(in) :: nsnr
@ -23,7 +23,7 @@ module qra66_decode
integer, intent(in) :: ntrperiod integer, intent(in) :: ntrperiod
real, intent(in) :: fmid real, intent(in) :: fmid
real, intent(in) :: w50 real, intent(in) :: w50
end subroutine qra66_decode_callback end subroutine qra65_decode_callback
end interface end interface
contains contains
@ -35,8 +35,8 @@ contains
use packjt use packjt
use, intrinsic :: iso_c_binding use, intrinsic :: iso_c_binding
parameter (NMAX=300*12000) !### Needs to be 300*12000 ### parameter (NMAX=300*12000) !### Needs to be 300*12000 ###
class(qra66_decoder), intent(inout) :: this class(qra65_decoder), intent(inout) :: this
procedure(qra66_decode_callback) :: callback procedure(qra65_decode_callback) :: callback
character(len=12) :: mycall, hiscall character(len=12) :: mycall, hiscall
character(len=6) :: hisgrid character(len=6) :: hisgrid
character*37 decoded character*37 decoded
@ -50,7 +50,7 @@ contains
data nc1z/-1/,nc2z/-1/,ng2z/-1/,maxaptypez/-1/,nsubmodez/-1/ data nc1z/-1/,nc2z/-1/,ng2z/-1/,maxaptypez/-1/,nsubmodez/-1/
save nc1z,nc2z,ng2z,maxaptypez,nsave,nsubmodez save nc1z,nc2z,ng2z,maxaptypez,nsave,nsubmodez
mode66=2**nsubmode mode65=2**nsubmode
nfft1=ntrperiod*12000 nfft1=ntrperiod*12000
nfft2=ntrperiod*6000 nfft2=ntrperiod*6000
allocate (c0(0:nfft1-1)) allocate (c0(0:nfft1-1))
@ -58,8 +58,8 @@ contains
if(nsubmode.ne.nsubmodez) then if(nsubmode.ne.nsubmodez) then
if(allocated(s3)) deallocate(s3) if(allocated(s3)) deallocate(s3)
if(allocated(s3a)) deallocate(s3a) if(allocated(s3a)) deallocate(s3a)
allocate(s3(-64:64*mode66+63,63)) allocate(s3(-64:64*mode65+63,63))
allocate(s3a(-64:64*mode66+63,63)) allocate(s3a(-64:64*mode65+63,63))
endif endif
if(ntrperiod.eq.15) then if(ntrperiod.eq.15) then
@ -115,9 +115,9 @@ contains
endif endif
naptype=maxaptype naptype=maxaptype
call timer('sync66 ',0) call timer('sync_q65',0)
call sync66(iwave,ntrperiod*12000,mode66,nsps,nfqso,ntol,xdt,f0,snr1) call sync_qra65(iwave,ntrperiod*12000,mode65,nsps,nfqso,ntol,xdt,f0,snr1)
call timer('sync66 ',1) call timer('sync_q65',1)
! Downsample to give complex data at 6000 S/s ! Downsample to give complex data at 6000 S/s
fac=2.0/nfft1 fac=2.0/nfft1
@ -131,20 +131,20 @@ contains
if(ntrperiod.ge.60) jpk=(xdt+1.0)*6000 - 384 !### TBD ### if(ntrperiod.ge.60) jpk=(xdt+1.0)*6000 - 384 !### TBD ###
if(jpk.lt.0) jpk=0 if(jpk.lt.0) jpk=0
a=0. a=0.
a(1)=-(f0 + mode66*baud) !Data tones start mode66 bins higher a(1)=-(f0 + mode65*baud) !Data tones start mode65 bins higher
call twkfreq(c0,c0,ntrperiod*6000,6000.0,a) call twkfreq(c0,c0,ntrperiod*6000,6000.0,a)
xdt=jpk/6000.0 - 0.5 xdt=jpk/6000.0 - 0.5
LL=64*(mode66+2) LL=64*(mode65+2)
NN=63 NN=63
call spec66(c0(jpk:),nsps/2,s3,LL,NN) !Compute synchronized symbol spectra call spec_qra65(c0(jpk:),nsps/2,s3,LL,NN) !Compute synchronized symbol spectra
do j=1,63 !Normalize to symbol baseline do j=1,63 !Normalize to symbol baseline
call pctile(s3(:,j),LL,40,base) call pctile(s3(:,j),LL,40,base)
s3(:,j)=s3(:,j)/base s3(:,j)=s3(:,j)/base
enddo enddo
LL2=64*(mode66+1)-1 LL2=64*(mode65+1)-1
s3max=20.0 s3max=20.0
do j=1,63 !Apply AGC to suppress pings do j=1,63 !Apply AGC to suppress pings
xx=maxval(s3(-64:LL2,j)) xx=maxval(s3(-64:LL2,j))
@ -201,4 +201,4 @@ contains
return return
end subroutine decode end subroutine decode
end module qra66_decode end module qra65_decode

View File

@ -1,4 +1,4 @@
subroutine spec66(c0,nsps,s3,LL,NN) subroutine spec_qra65(c0,nsps,s3,LL,NN)
! Compute synchronized symbol spectra. ! Compute synchronized symbol spectra.
@ -46,4 +46,4 @@ subroutine spec66(c0,nsps,s3,LL,NN)
enddo enddo
return return
end subroutine spec66 end subroutine spec_qra65

View File

@ -1,4 +1,4 @@
subroutine sync66(iwave,nmax,mode66,nsps,nfqso,ntol,xdt,f0,snr1) subroutine sync_qra65(iwave,nmax,mode65,nsps,nfqso,ntol,xdt,f0,snr1)
parameter (NSTEP=4) !Quarter-symbol steps parameter (NSTEP=4) !Quarter-symbol steps
integer*2 iwave(0:nmax-1) !Raw data integer*2 iwave(0:nmax-1) !Raw data
@ -7,7 +7,7 @@ subroutine sync66(iwave,nmax,mode66,nsps,nfqso,ntol,xdt,f0,snr1)
real, allocatable :: s1(:,:) !Symbol spectra, quarter-symbol steps real, allocatable :: s1(:,:) !Symbol spectra, quarter-symbol steps
real sync(85) !sync vector real sync(85) !sync vector
real ccf(-64:64,-15:15) real ccf(-64:64,-15:15)
complex, allocatable :: c0(:) !Complex spectrum of symbol complex, allocatable :: c0(:) !Complex spectrum of symbol
data isync/1,9,12,13,15,22,23,26,27,33,35,38,46,50,55,60,62,66,69,74,76,85/ data isync/1,9,12,13,15,22,23,26,27,33,35,38,46,50,55,60,62,66,69,74,76,85/
data sync(1)/99.0/ data sync(1)/99.0/
save sync save sync
@ -72,6 +72,9 @@ subroutine sync66(iwave,nmax,mode66,nsps,nfqso,ntol,xdt,f0,snr1)
if(nsps.ge.7680) jadd=6 if(nsps.ge.7680) jadd=6
if(nsps.ge.16000) jadd=3 if(nsps.ge.16000) jadd=3
if(nsps.ge.41472) jadd=1 if(nsps.ge.41472) jadd=1
dt4=nsps/(NSTEP*12000.0) !1/4 of symbol duration
! j0=0.5/dt4
! if(nsps.ge.7680) j0=1.0/dt4
do i=-ia,ia do i=-ia,ia
do lag=-15,15 do lag=-15,15
@ -96,8 +99,6 @@ subroutine sync66(iwave,nmax,mode66,nsps,nfqso,ntol,xdt,f0,snr1)
ijpk=maxloc(ccf) ijpk=maxloc(ccf)
ipk=ijpk(1)-65 ipk=ijpk(1)-65
jpk=ijpk(2)-16 jpk=ijpk(2)-16
dt4=nsps/(NSTEP*12000.0) !1/4 of symbol duration
if(nsps.ge.7680) j0=1.0/dt4
f0=nfqso + ipk*df f0=nfqso + ipk*df
xdt=jpk*dt4 xdt=jpk*dt4
snr1=maxval(ccf)/22.0 snr1=maxval(ccf)/22.0
@ -105,4 +106,4 @@ subroutine sync66(iwave,nmax,mode66,nsps,nfqso,ntol,xdt,f0,snr1)
!3100 format(2i5,f7.2,2f10.2) !3100 format(2i5,f7.2,2f10.2)
return return
end subroutine sync66 end subroutine sync_qra65