mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2025-03-21 03:28:59 -04:00
Change mode name QRA65 to Q65 everywhere, supposedly.
This commit is contained in:
parent
90fb84e43e
commit
9b452e8f99
@ -324,7 +324,7 @@ set (wsjt_FSRCS
|
||||
lib/options.f90
|
||||
lib/packjt.f90
|
||||
lib/77bit/packjt77.f90
|
||||
lib/qra65_decode.f90
|
||||
lib/q65_decode.f90
|
||||
lib/readwav.f90
|
||||
lib/timer_C_wrapper.f90
|
||||
lib/timer_impl.f90
|
||||
@ -525,7 +525,7 @@ set (wsjt_FSRCS
|
||||
lib/sync4.f90
|
||||
lib/sync64.f90
|
||||
lib/sync65.f90
|
||||
lib/sync_qra65.f90
|
||||
lib/sync_q65.f90
|
||||
lib/ft4/getcandidates4.f90
|
||||
lib/ft4/get_ft4_bitmetrics.f90
|
||||
lib/ft8/sync8.f90
|
||||
@ -1114,14 +1114,14 @@ target_link_libraries (sumsim wsjt_fort wsjt_cxx)
|
||||
add_executable (qra64sim lib/qra/qra64/qra64sim.f90)
|
||||
target_link_libraries (qra64sim wsjt_fort wsjt_cxx)
|
||||
|
||||
add_executable (qra65sim lib/qra/qra65/qra65sim.f90)
|
||||
target_link_libraries (qra65sim wsjt_fort wsjt_cxx)
|
||||
add_executable (q65sim lib/qra/qra65/q65sim.f90)
|
||||
target_link_libraries (q65sim wsjt_fort wsjt_cxx)
|
||||
|
||||
add_executable (test_qra64 lib/test_qra64.f90)
|
||||
target_link_libraries (test_qra64 wsjt_fort wsjt_cxx)
|
||||
|
||||
add_executable (test_qra65 lib/test_qra65.f90)
|
||||
target_link_libraries (test_qra65 wsjt_fort wsjt_cxx)
|
||||
add_executable (test_q65 lib/test_q65.f90)
|
||||
target_link_libraries (test_q65 wsjt_fort wsjt_cxx)
|
||||
|
||||
add_executable (jt49sim lib/jt49sim.f90)
|
||||
target_link_libraries (jt49sim wsjt_fort wsjt_cxx)
|
||||
@ -1545,7 +1545,7 @@ install (TARGETS jt9 wsprd fmtave fcal fmeasure
|
||||
|
||||
if(WSJT_BUILD_UTILS)
|
||||
install (TARGETS ft8code jt65code qra64code qra64sim jt9code jt4code
|
||||
msk144code fst4sim qra65sim
|
||||
msk144code fst4sim q65sim
|
||||
RUNTIME DESTINATION ${CMAKE_INSTALL_BINDIR} COMPONENT runtime
|
||||
BUNDLE DESTINATION ${CMAKE_INSTALL_BINDIR} COMPONENT runtime
|
||||
)
|
||||
|
@ -70,7 +70,8 @@ void Modulator::start (QString mode, unsigned symbolsLength, double framesPerSym
|
||||
m_bFastMode=fastMode;
|
||||
m_TRperiod=TRperiod;
|
||||
unsigned delay_ms=1000;
|
||||
if(mode=="FT8" or (mode=="FST4" and m_nsps==720) or mode=="QRA65") delay_ms=500; //FT8, FST4-15, QRA65
|
||||
if(mode=="FT8" or (mode=="FST4" and m_nsps==720)) delay_ms=500; //FT8, FST4-15
|
||||
if(mode=="Q65" and m_nsps<=3600) delay_ms=500; //Q65-15 and Q65-30
|
||||
if(mode=="FT4") delay_ms=300; //FT4
|
||||
|
||||
// noise generator parameters
|
||||
|
@ -9,7 +9,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
|
||||
use ft8_decode
|
||||
use ft4_decode
|
||||
use fst4_decode
|
||||
use qra65_decode
|
||||
use q65_decode
|
||||
|
||||
include 'jt9com.f90'
|
||||
include 'timer_common.inc'
|
||||
@ -38,9 +38,9 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
|
||||
integer :: decoded
|
||||
end type counting_fst4_decoder
|
||||
|
||||
type, extends(qra65_decoder) :: counting_qra65_decoder
|
||||
type, extends(q65_decoder) :: counting_q65_decoder
|
||||
integer :: decoded
|
||||
end type counting_qra65_decoder
|
||||
end type counting_q65_decoder
|
||||
|
||||
real ss(184,NSMAX)
|
||||
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_ft4_decoder) :: my_ft4
|
||||
type(counting_fst4_decoder) :: my_fst4
|
||||
type(counting_qra65_decoder) :: my_qra65
|
||||
type(counting_q65_decoder) :: my_q65
|
||||
|
||||
rms=sqrt(dot_product(float(id2(1:180000)), &
|
||||
float(id2(1:180000)))/180000.0)
|
||||
@ -79,7 +79,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
|
||||
my_ft8%decoded = 0
|
||||
my_ft4%decoded = 0
|
||||
my_fst4%decoded = 0
|
||||
my_qra65%decoded = 0
|
||||
my_q65%decoded = 0
|
||||
|
||||
! For testing only: return Rx messages stored in a file as decodes
|
||||
inquire(file='rx_messages.txt',exist=ex)
|
||||
@ -198,13 +198,13 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
|
||||
go to 800
|
||||
endif
|
||||
|
||||
if(params%nmode.eq.66) then !NB: JT65 = 65, QRA65 = 66.
|
||||
! We're in QRA65 mode
|
||||
call timer('decqra65',0)
|
||||
call my_qra65%decode(qra65_decoded,id2,params%nutc,params%ntr, &
|
||||
if(params%nmode.eq.66) then !NB: JT65 = 65, Q65 = 66.
|
||||
! We're in Q65 mode
|
||||
call timer('dec_q65 ',0)
|
||||
call my_q65%decode(q65_decoded,id2,params%nutc,params%ntr, &
|
||||
params%nsubmode,params%nfqso,params%ntol,params%ndepth, &
|
||||
mycall,hiscall,hisgrid)
|
||||
call timer('decqra65',1)
|
||||
call timer('dec_q65 ',1)
|
||||
go to 800
|
||||
endif
|
||||
|
||||
@ -213,13 +213,13 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
|
||||
ndepth=iand(params%ndepth,3)
|
||||
iwspr=0
|
||||
params%nsubmode=0
|
||||
call timer('dec240 ',0)
|
||||
call timer('dec_fst4',0)
|
||||
call my_fst4%decode(fst4_decoded,id2,params%nutc, &
|
||||
params%nQSOProgress,params%nfa,params%nfb, &
|
||||
params%nfqso,ndepth,params%ntr,params%nexp_decode, &
|
||||
params%ntol,params%emedelay,logical(params%nagain), &
|
||||
logical(params%lapcqonly),mycall,hiscall,iwspr)
|
||||
call timer('dec240 ',1)
|
||||
call timer('dec_fst4',1)
|
||||
go to 800
|
||||
endif
|
||||
|
||||
@ -227,13 +227,13 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
|
||||
! We're in FST4W mode
|
||||
ndepth=iand(params%ndepth,3)
|
||||
iwspr=1
|
||||
call timer('dec240 ',0)
|
||||
call timer('dec_fst4',0)
|
||||
call my_fst4%decode(fst4_decoded,id2,params%nutc, &
|
||||
params%nQSOProgress,params%nfa,params%nfb, &
|
||||
params%nfqso,ndepth,params%ntr,params%nexp_decode, &
|
||||
params%ntol,params%emedelay,logical(params%nagain), &
|
||||
logical(params%lapcqonly),mycall,hiscall,iwspr)
|
||||
call timer('dec240 ',1)
|
||||
call timer('dec_fst4',1)
|
||||
go to 800
|
||||
endif
|
||||
|
||||
@ -776,13 +776,13 @@ contains
|
||||
return
|
||||
end subroutine fst4_decoded
|
||||
|
||||
subroutine qra65_decoded (this,nutc,sync,nsnr,dt,freq,decoded,irc, &
|
||||
subroutine q65_decoded (this,nutc,sync,nsnr,dt,freq,decoded,irc, &
|
||||
qual,ntrperiod,fmid,w50)
|
||||
|
||||
use qra65_decode
|
||||
use q65_decode
|
||||
implicit none
|
||||
|
||||
class(qra65_decoder), intent(inout) :: this
|
||||
class(q65_decoder), intent(inout) :: this
|
||||
integer, intent(in) :: nutc
|
||||
real, intent(in) :: sync
|
||||
integer, intent(in) :: nsnr
|
||||
@ -801,23 +801,23 @@ contains
|
||||
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)
|
||||
write(13,1002) nutc,nint(sync),nsnr,dt,freq,0,decoded
|
||||
1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a37,' QRA65')
|
||||
1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a37,' Q65')
|
||||
else
|
||||
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)
|
||||
write(13,1004) nutc,nint(sync),nsnr,dt,freq,0,decoded
|
||||
1004 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a37,' QRA65')
|
||||
1004 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a37,' Q65')
|
||||
|
||||
endif
|
||||
call flush(6)
|
||||
call flush(13)
|
||||
|
||||
select type(this)
|
||||
type is (counting_qra65_decoder)
|
||||
type is (counting_q65_decoder)
|
||||
this%decoded = this%decoded + 1
|
||||
end select
|
||||
|
||||
return
|
||||
end subroutine qra65_decoded
|
||||
end subroutine q65_decoded
|
||||
|
||||
end subroutine multimode_decoder
|
||||
|
@ -1,17 +1,17 @@
|
||||
module qra65_decode
|
||||
module q65_decode
|
||||
|
||||
type :: qra65_decoder
|
||||
procedure(qra65_decode_callback), pointer :: callback
|
||||
type :: q65_decoder
|
||||
procedure(q65_decode_callback), pointer :: callback
|
||||
contains
|
||||
procedure :: decode
|
||||
end type qra65_decoder
|
||||
end type q65_decoder
|
||||
|
||||
abstract interface
|
||||
subroutine qra65_decode_callback (this,nutc,sync,nsnr,dt,freq, &
|
||||
subroutine q65_decode_callback (this,nutc,sync,nsnr,dt,freq, &
|
||||
decoded,nap,qual,ntrperiod,fmid,w50)
|
||||
import qra65_decoder
|
||||
import q65_decoder
|
||||
implicit none
|
||||
class(qra65_decoder), intent(inout) :: this
|
||||
class(q65_decoder), intent(inout) :: this
|
||||
integer, intent(in) :: nutc
|
||||
real, intent(in) :: sync
|
||||
integer, intent(in) :: nsnr
|
||||
@ -23,7 +23,7 @@ module qra65_decode
|
||||
integer, intent(in) :: ntrperiod
|
||||
real, intent(in) :: fmid
|
||||
real, intent(in) :: w50
|
||||
end subroutine qra65_decode_callback
|
||||
end subroutine q65_decode_callback
|
||||
end interface
|
||||
|
||||
contains
|
||||
@ -31,7 +31,7 @@ contains
|
||||
subroutine decode(this,callback,iwave,nutc,ntrperiod,nsubmode,nfqso, &
|
||||
ntol,ndepth,mycall,hiscall,hisgrid)
|
||||
|
||||
! Decodes QRA65 signals
|
||||
! Decodes Q65 signals
|
||||
! Input: iwave Raw data, i*2
|
||||
! nutc UTC for time-tagging the decode
|
||||
! ntrperiod T/R sequence length (s)
|
||||
@ -45,8 +45,8 @@ contains
|
||||
use packjt
|
||||
use, intrinsic :: iso_c_binding
|
||||
parameter (NMAX=300*12000) !Max TRperiod is 300 s
|
||||
class(qra65_decoder), intent(inout) :: this
|
||||
procedure(qra65_decode_callback) :: callback
|
||||
class(q65_decoder), intent(inout) :: this
|
||||
procedure(q65_decode_callback) :: callback
|
||||
character(len=12) :: mycall, hiscall !Used for AP decoding
|
||||
character(len=6) :: hisgrid
|
||||
character*37 decoded !Decoded message
|
||||
@ -98,7 +98,7 @@ contains
|
||||
! if(ndepth.eq.3) maxaptype=5
|
||||
if(ndepth.ge.2) maxaptype=5 !###
|
||||
minsync=-2
|
||||
call qra_params(ndepth,maxaptype,idfmax,idtmax,ibwmin,ibwmax)
|
||||
call qra_params(ndepth,maxaptype,idfmax,idtmax,ibwmin,ibwmax,maxdist)
|
||||
|
||||
if(nc1.ne.nc1z .or. nc2.ne.nc2z .or. ng2.ne.ng2z .or. &
|
||||
maxaptype.ne.maxaptypez) then
|
||||
@ -115,7 +115,7 @@ contains
|
||||
naptype=maxaptype
|
||||
|
||||
call timer('sync_q65',0)
|
||||
call sync_qra65(iwave,ntrperiod*12000,mode65,nsps,nfqso,ntol,xdt,f0,snr1)
|
||||
call sync_q65(iwave,ntrperiod*12000,mode65,nsps,nfqso,ntol,xdt,f0,snr1)
|
||||
call timer('sync_q65',1)
|
||||
|
||||
irc=-1
|
||||
@ -159,4 +159,4 @@ contains
|
||||
return
|
||||
end subroutine decode
|
||||
|
||||
end module qra65_decode
|
||||
end module q65_decode
|
20
lib/q65params.f90
Normal file
20
lib/q65params.f90
Normal file
@ -0,0 +1,20 @@
|
||||
program q65params
|
||||
|
||||
integer ntrp(5)
|
||||
integer nsps(5)
|
||||
data ntrp/15,30,60,120,300/
|
||||
data nsps/1800,3600,7200,15680,40960/
|
||||
|
||||
write(*,1000)
|
||||
1000 format('T/R tsym baud BW TxT SNR'/39('-'))
|
||||
do i=1,5
|
||||
baud=12000.0/nsps(i)
|
||||
bw=65.0*baud
|
||||
tsym=1.0/baud
|
||||
txt=85.0*tsym
|
||||
snr=-27.0 + 10.0*log10(7200.0/nsps(i))
|
||||
write(*,1010) ntrp(i),tsym,baud,bw,txt,snr
|
||||
1010 format(i3,2f7.3,3f7.1)
|
||||
enddo
|
||||
|
||||
end program q65params
|
@ -1,6 +1,6 @@
|
||||
program qra65sim
|
||||
program q65sim
|
||||
|
||||
! Generate simulated QRA65 data for testing the decoder.
|
||||
! Generate simulated Q65 data for testing the decoder.
|
||||
|
||||
use wavhdr
|
||||
use packjt
|
||||
@ -21,8 +21,8 @@ program qra65sim
|
||||
|
||||
nargs=iargc()
|
||||
if(nargs.ne.9) then
|
||||
print *, 'Usage: qra65sim "msg" A-E freq fDop DT TRp Nfiles Sync SNR'
|
||||
print *, 'Example: qra65sim "K1ABC W9XYZ EN37" A 1500 0.0 0.0 60 1 T -26'
|
||||
print *, 'Usage: q65sim "msg" A-E freq fDop DT TRp Nfiles Sync SNR'
|
||||
print *, 'Example: q65sim "K1ABC W9XYZ EN37" A 1500 0.0 0.0 60 1 T -26'
|
||||
print*,'Sync = T to include sync test.'
|
||||
go to 999
|
||||
endif
|
||||
@ -185,7 +185,7 @@ program qra65sim
|
||||
if(ifile.eq.nfiles) cd='d'
|
||||
nfqso=nint(f0)
|
||||
ntol=100
|
||||
call sync_qra65(iwave,npts,mode65,nsps,nfqso,ntol,xdt2,f02,snr2)
|
||||
call sync_q65(iwave,npts,mode65,nsps,nfqso,ntol,xdt2,f02,snr2)
|
||||
terr=1.01/(8.0*baud)
|
||||
ferr=1.01*mode65*baud
|
||||
if(abs(xdt2-xdt).lt.terr .and. abs(f02-f0).lt.ferr) nsync=nsync+1
|
||||
@ -199,4 +199,4 @@ program qra65sim
|
||||
if(lsync) write(*,1040) snrdb,nfiles,nsync
|
||||
1040 format('SNR:',f6.1,' nfiles:',i5,' nsynced:',i5)
|
||||
|
||||
999 end program qra65sim
|
||||
999 end program q65sim
|
@ -37,7 +37,7 @@ subroutine qra64a(dd,npts,nf1,nf2,nfqso,ntol,mode64,minsync,ndepth, &
|
||||
nFadingModel=1
|
||||
maxaptype=4
|
||||
if(iand(ndepth,64).ne.0) maxaptype=5
|
||||
call qra_params(ndepth,maxaptype,idfmax,idtmax,ibwmin,ibwmax)
|
||||
call qra_params(ndepth,maxaptype,idfmax,idtmax,ibwmin,ibwmax,maxdist)
|
||||
if(nc1.ne.nc1z .or. nc2.ne.nc2z .or. ng2.ne.ng2z .or. &
|
||||
maxaptype.ne.maxaptypez) then
|
||||
do naptype=0,maxaptype
|
||||
@ -96,14 +96,14 @@ subroutine qra64a(dd,npts,nf1,nf2,nfqso,ntol,mode64,minsync,ndepth, &
|
||||
return
|
||||
end subroutine qra64a
|
||||
|
||||
subroutine qra_params(ndepth,maxaptype,idf0max,idt0max,ibwmin,ibwmax)
|
||||
subroutine qra_params(ndepth,maxaptype,idf0max,idt0max,ibwmin,ibwmax,maxdist)
|
||||
|
||||
! If file qra_params is present in CWD, read decoding params from it.
|
||||
|
||||
integer iparam(6)
|
||||
integer iparam(7)
|
||||
logical first,ex
|
||||
! data iparam/3,5,3,11,0,9/ !Maximum effort
|
||||
data iparam/2,5,3,11,3,9/ !Default values
|
||||
! data iparam/3,5,3,11,0,9,30/ !Maximum effort
|
||||
data iparam/2,5,3,11,3,9,10/ !Default values
|
||||
data first/.true./
|
||||
save first,iparam
|
||||
|
||||
@ -122,6 +122,7 @@ subroutine qra_params(ndepth,maxaptype,idf0max,idt0max,ibwmin,ibwmax)
|
||||
idt0max=iparam(4)
|
||||
ibwmin=iparam(5)
|
||||
ibwmax=iparam(6)
|
||||
|
||||
maxdist=iparam(7)
|
||||
|
||||
return
|
||||
end subroutine qra_params
|
||||
|
@ -22,14 +22,11 @@ subroutine qra_loops(c00,npts2,nsps,mode,mode64,nsubmode,nFadingModel, &
|
||||
if(mode64.le.4) ibwmax=9
|
||||
ibwmin=ibwmax
|
||||
idtmax=3
|
||||
call qra_params(ndepth,maxaptype,idfmax,idtmax,ibwmin,ibwmax)
|
||||
call qra_params(ndepth,maxaptype,idfmax,idtmax,ibwmin,ibwmax,maxdist)
|
||||
LL=64*(mode64+2)
|
||||
NN=63
|
||||
napmin=99
|
||||
ncall=0
|
||||
maxdist=5
|
||||
if(ndepth.eq.2) maxdist=10
|
||||
if(ndepth.eq.3) maxdist=30
|
||||
|
||||
do iavg=0,1
|
||||
if(iavg.eq.1) then
|
||||
@ -95,8 +92,9 @@ subroutine qra_loops(c00,npts2,nsps,mode,mode64,nsubmode,nFadingModel, &
|
||||
a=0.
|
||||
a(1)=-f0
|
||||
call twkfreq(c00,c0,npts2,6000.0,a)
|
||||
! jpk=4320
|
||||
jpk=4080
|
||||
jpk=3000 !### These definitions need work ###
|
||||
! if(nsps.ge.3600) jpk=4080 !###
|
||||
if(nsps.ge.3600) jpk=6000 !###
|
||||
call spec64(c0,nsps,mode,mode64,jpk,s3,LL,NN)
|
||||
call pctile(s3,LL*NN,40,base)
|
||||
s3=s3/base
|
||||
|
@ -41,7 +41,7 @@ subroutine spec64(c0,nsps,mode,mode64,jpk,s3,LL,NN)
|
||||
cs(0:nfft-1)=fac*c0(ja:jb)
|
||||
call four2a(cs,nsps,1,-1,1) !c2c FFT to frequency
|
||||
do ii=1,LL
|
||||
i=ii-65+mode64 !mode64 = 1 2 4 8 16 for QRA65 A B C D E
|
||||
i=ii-65+mode64 !mode64 = 1 2 4 8 16 for Q65 A B C D E
|
||||
if(i.lt.0) i=i+nsps
|
||||
s3(ii,j)=real(cs(i))**2 + aimag(cs(i))**2
|
||||
enddo
|
||||
|
@ -1,6 +1,6 @@
|
||||
subroutine sync_qra65(iwave,nmax,mode65,nsps,nfqso,ntol,xdt,f0,snr1)
|
||||
subroutine sync_q65(iwave,nmax,mode65,nsps,nfqso,ntol,xdt,f0,snr1)
|
||||
|
||||
! Detect and align with the QRA65 sync vector, returning time and frequency
|
||||
! Detect and align with the Q65 sync vector, returning time and frequency
|
||||
! offsets and SNR estimate.
|
||||
|
||||
! Input: iwave(0:nmax-1) Raw data
|
||||
@ -121,4 +121,4 @@ subroutine sync_qra65(iwave,nmax,mode65,nsps,nfqso,ntol,xdt,f0,snr1)
|
||||
! enddo
|
||||
|
||||
return
|
||||
end subroutine sync_qra65
|
||||
end subroutine sync_q65
|
@ -1,4 +1,4 @@
|
||||
program test_qra65
|
||||
program test_q65
|
||||
|
||||
character*73 cmd1,cmd2,line
|
||||
character*22 msg
|
||||
@ -9,8 +9,8 @@ program test_qra65
|
||||
|
||||
nargs=iargc()
|
||||
if(nargs.ne.9) then
|
||||
print*,'Usage: test_qra65 "msg" A-D depth freq DT fDop TRp nfiles SNR'
|
||||
print*,'Example: test_qra65 "K1ABC W9XYZ EN37" A 3 1500 0.0 5.0 60 100 -20'
|
||||
print*,'Usage: test_q65 "msg" A-D depth freq DT fDop TRp nfiles SNR'
|
||||
print*,'Example: test_q65 "K1ABC W9XYZ EN37" A 3 1500 0.0 5.0 60 100 -20'
|
||||
print*,' SNR = 0 to loop over all relevant SNRs'
|
||||
go to 999
|
||||
endif
|
||||
@ -61,7 +61,7 @@ program test_qra65
|
||||
|
||||
! 1 2 3 4 5 6 7
|
||||
! 1234567890123456789012345678901234567890123456789012345678901234567890123'
|
||||
cmd1='qra65sim "K1ABC W9XYZ EN37 " A 1500 5.0 0.0 60 100 F -10 > junk0'
|
||||
cmd1='q65sim "K1ABC W9XYZ EN37 " A 1500 5.0 0.0 60 100 F -10 > junk0'
|
||||
cmd2='jt9 -3 -p 15 -L 300 -H 3000 -d 3 -b A *.wav > junk'
|
||||
|
||||
write(cmd1(10:33),'(a)') '"'//msg//'"'
|
||||
@ -71,25 +71,32 @@ program test_qra65
|
||||
write(cmd1(46:50),'(f5.2)') dt
|
||||
write(cmd1(51:54),'(i4)') ntrperiod
|
||||
write(cmd1(55:59),'(i5)') nfiles
|
||||
|
||||
write(cmd2(11:13),'(i3)') ntrperiod
|
||||
write(cmd2(33:33),'(i1)') ndepth
|
||||
cmd2(38:38)=csubmode
|
||||
call system('rm -f *.wav')
|
||||
|
||||
write(*,1000) (j,j=0,11)
|
||||
write(12,1000) (j,j=0,11)
|
||||
1000 format(/'SNR d Dop Sync Dec1 DecN Bad',i6,11i4,' tdec'/85('-'))
|
||||
call qra_params(ndepth,maxaptype,idf0max,idt0max,ibwmin,ibwmax,maxdist)
|
||||
write(*,1000) ndepth,maxaptype,idf0max,idt0max,ibwmin,ibwmax,maxdist
|
||||
write(12,1000) ndepth,maxaptype,idf0max,idt0max,ibwmin,ibwmax,maxdist
|
||||
1000 format(/'Depth:',i2,' AP:',i2,' df:',i3,' dt:',i3,' bw1:',i3,' bw2:',i3, &
|
||||
' dist:',i3)
|
||||
|
||||
write(*,1010) (j,j=0,11)
|
||||
write(12,1010) (j,j=0,11)
|
||||
1010 format('SNR d Dop Sync DecN Dec1 Bad',i6,11i4,' tdec'/85('-'))
|
||||
|
||||
dterr=tsym/4.0
|
||||
nferr=max(1,nint(0.5*baud),nint(fdop/3.0))
|
||||
ndecodes0=nfiles
|
||||
ndec10=nfiles
|
||||
|
||||
do nsnr=ia,ib,-1
|
||||
nsync=0
|
||||
ndecodes=0
|
||||
ndec1=0
|
||||
nfalse=0
|
||||
nretcode=0
|
||||
navg=0
|
||||
ndecn=0
|
||||
write(cmd1(63:65),'(i3)') nsnr
|
||||
call system(cmd1)
|
||||
call sec0(0,tdec)
|
||||
@ -107,18 +114,15 @@ program test_qra65
|
||||
nsync=nsync+1
|
||||
endif
|
||||
irc=-1
|
||||
if(line(23:23).ne.' ') read(line(60:),*) irc,iavg
|
||||
iavg=0
|
||||
i0=23
|
||||
if(ntrperiod.le.30) i0=25
|
||||
if(line(i0:i0).ne.' ') read(line(60:),*) irc,iavg
|
||||
if(irc.lt.0) cycle
|
||||
if(decok) then
|
||||
i=irc
|
||||
if(i.le.11) then
|
||||
ndecodes=ndecodes + 1
|
||||
navg=navg + 1
|
||||
else
|
||||
i=mod(i,10)
|
||||
navg=navg + 1
|
||||
endif
|
||||
nretcode(i)=nretcode(i) + 1
|
||||
ndecn=ndecn + 1
|
||||
if(iavg.le.1) ndec1=ndec1 + 1
|
||||
nretcode(irc)=nretcode(irc) + 1
|
||||
else
|
||||
nfalse=nfalse + 1
|
||||
print*,'False: ',line
|
||||
@ -127,24 +131,24 @@ program test_qra65
|
||||
10 close(10)
|
||||
xdt_avg=0.
|
||||
xdt_rms=0.
|
||||
write(*,1100) nsnr,ndepth,fDop,nsync,ndecodes,navg,nfalse,nretcode, &
|
||||
write(*,1100) nsnr,ndepth,fDop,nsync,ndecn,ndec1,nfalse,nretcode, &
|
||||
tdec/nfiles
|
||||
write(12,1100) nsnr,ndepth,fDop,nsync,ndecodes,navg,nfalse,nretcode, &
|
||||
write(12,1100) nsnr,ndepth,fDop,nsync,ndecn,ndec1,nfalse,nretcode, &
|
||||
tdec/nfiles
|
||||
1100 format(i3,i2,f5.1,3i5,i4,i6,11i4,f6.2)
|
||||
if(ndecodes.lt.nfiles/2 .and. ndecodes0.ge.nfiles/2) then
|
||||
snr_thresh=nsnr + float(nfiles/2 - ndecodes)/(ndecodes0-ndecodes)
|
||||
if(ndec1.lt.nfiles/2 .and. ndec10.ge.nfiles/2) then
|
||||
snr_thresh=nsnr + float(nfiles/2 - ndec1)/(ndec10-ndec1)
|
||||
write(13,1200) ndepth,fdop,csubmode,snr_thresh
|
||||
1200 format(i1,f6.1,2x,a1,f7.1)
|
||||
flush(13)
|
||||
endif
|
||||
flush(6)
|
||||
flush(12)
|
||||
if(ndecodes.eq.0) exit !Bail out if no decodes at this SNR
|
||||
ndecodes0=ndecodes
|
||||
if(ndec1.eq.0 .and. ndecn.eq.0) exit !Bail out if no decodes at this SNR
|
||||
ndec10=ndec1
|
||||
enddo ! nsnr
|
||||
|
||||
999 end program test_qra65
|
||||
999 end program test_q65
|
||||
|
||||
include 'sec0.f90'
|
||||
include 'sec0.f90'
|
||||
|
@ -263,7 +263,7 @@ namespace
|
||||
|
||||
{50200000, Modes::Echo, IARURegions::ALL},
|
||||
{50270000, Modes::QRA64, IARURegions::ALL},
|
||||
{50270000, Modes::QRA65, IARURegions::ALL},
|
||||
{50270000, Modes::Q65, IARURegions::ALL},
|
||||
{50276000, Modes::JT65, IARURegions::R2},
|
||||
{50276000, Modes::JT65, IARURegions::R3},
|
||||
{50380000, Modes::MSK144, IARURegions::R1},
|
||||
|
@ -27,7 +27,7 @@ namespace
|
||||
"FT4",
|
||||
"FST4",
|
||||
"FST4W",
|
||||
"QRA65"
|
||||
"Q65"
|
||||
};
|
||||
std::size_t constexpr mode_names_size = sizeof (mode_names) / sizeof (mode_names[0]);
|
||||
}
|
||||
|
@ -52,7 +52,7 @@ public:
|
||||
FT4,
|
||||
FST4,
|
||||
FST4W,
|
||||
QRA65,
|
||||
Q65,
|
||||
MODES_END_SENTINAL_AND_COUNT // this must be last
|
||||
};
|
||||
Q_ENUM (Mode)
|
||||
|
@ -602,7 +602,7 @@ MainWindow::MainWindow(QDir const& temp_directory, bool multiple,
|
||||
ui->actionISCAT->setActionGroup(modeGroup);
|
||||
ui->actionMSK144->setActionGroup(modeGroup);
|
||||
ui->actionQRA64->setActionGroup(modeGroup);
|
||||
ui->actionQRA65->setActionGroup(modeGroup);
|
||||
ui->actionQ65->setActionGroup(modeGroup);
|
||||
ui->actionFreqCal->setActionGroup(modeGroup);
|
||||
|
||||
QActionGroup* saveGroup = new QActionGroup(this);
|
||||
@ -1382,7 +1382,7 @@ void MainWindow::fixStop()
|
||||
} else if (m_mode=="QRA64"){
|
||||
m_hsymStop=179;
|
||||
if(m_config.decode_at_52s()) m_hsymStop=186;
|
||||
} else if (m_mode=="QRA65"){
|
||||
} else if (m_mode=="Q65"){
|
||||
m_hsymStop=48;
|
||||
if(m_TRperiod==30) m_hsymStop=96;
|
||||
if(m_TRperiod==60) m_hsymStop=196;
|
||||
@ -2379,7 +2379,7 @@ void MainWindow::setup_status_bar (bool vhf)
|
||||
mode_label.setStyleSheet ("QLabel{color: #000000; background-color: #66ff66}");
|
||||
} else if ("QRA64" == m_mode) {
|
||||
mode_label.setStyleSheet ("QLabel{color: #000000; background-color: #99ff33}");
|
||||
} else if ("QRA65" == m_mode) {
|
||||
} else if ("Q65" == m_mode) {
|
||||
mode_label.setStyleSheet ("QLabel{color: #000000; background-color: #99ff33}");
|
||||
} else if ("MSK144" == m_mode) {
|
||||
mode_label.setStyleSheet ("QLabel{color: #000000; background-color: #ff6666}");
|
||||
@ -2581,7 +2581,7 @@ void MainWindow::on_actionCopyright_Notice_triggered()
|
||||
"notice prominently in your derivative work:\n\n"
|
||||
"\"The algorithms, source code, look-and-feel of WSJT-X and related "
|
||||
"programs, and protocol specifications for the modes FSK441, FST4, FT8, "
|
||||
"JT4, JT6M, JT9, JT65, JTMS, QRA64, QRA65, ISCAT, MSK144 are Copyright (C) "
|
||||
"JT4, JT6M, JT9, JT65, JTMS, QRA64, Q65, ISCAT, MSK144 are Copyright (C) "
|
||||
"2001-2020 by one or more of the following authors: Joseph Taylor, "
|
||||
"K1JT; Bill Somerville, G4WJS; Steven Franke, K9AN; Nico Palermo, "
|
||||
"IV3NWV; Greg Beam, KI7MT; Michael Black, W9MDB; Edson Pereira, PY2SDR; "
|
||||
@ -3110,8 +3110,8 @@ void MainWindow::decode() //decode()
|
||||
ui->actionEnable_AP_JT65->isChecked ();
|
||||
if(m_mode=="QRA64") dec_data.params.nmode=164;
|
||||
if(m_mode=="QRA64") dec_data.params.ntxmode=164;
|
||||
if(m_mode=="QRA65") dec_data.params.nmode=66;
|
||||
if(m_mode=="QRA65") dec_data.params.ntxmode=66;
|
||||
if(m_mode=="Q65") dec_data.params.nmode=66;
|
||||
if(m_mode=="Q65") dec_data.params.ntxmode=66;
|
||||
if(m_mode=="JT9+JT65") dec_data.params.nmode=9+65; // = 74
|
||||
if(m_mode=="JT4") {
|
||||
dec_data.params.nmode=4;
|
||||
@ -3434,7 +3434,7 @@ void MainWindow::readFromStdout() //readFromStdout
|
||||
//Right (Rx Frequency) window
|
||||
bool bDisplayRight=bAvgMsg;
|
||||
int audioFreq=decodedtext.frequencyOffset();
|
||||
if(m_mode=="FT8" or m_mode=="FT4" or m_mode=="FST4" or m_mode=="QRA65") {
|
||||
if(m_mode=="FT8" or m_mode=="FT4" or m_mode=="FST4" or m_mode=="Q65") {
|
||||
auto const& parts = decodedtext.string().remove("<").remove(">")
|
||||
.split (' ', SkipEmptyParts);
|
||||
if (parts.size() > 6) {
|
||||
@ -3517,7 +3517,7 @@ void MainWindow::readFromStdout() //readFromStdout
|
||||
|
||||
//### I think this is where we are preventing Hounds from spotting Fox ###
|
||||
if(m_mode!="FT8" or (SpecOp::HOUND != m_config.special_op_id())) {
|
||||
if(m_mode=="FT8" or m_mode=="FT4" or m_mode=="QRA64" or m_mode=="QRA65"
|
||||
if(m_mode=="FT8" or m_mode=="FT4" or m_mode=="QRA64" or m_mode=="Q65"
|
||||
or m_mode=="JT4" or m_mode=="JT65" or m_mode=="JT9" or m_mode=="FST4") {
|
||||
auto_sequence (decodedtext, 25, 50);
|
||||
}
|
||||
@ -3727,7 +3727,7 @@ void MainWindow::guiUpdate()
|
||||
if(m_modeTx=="JT9") txDuration=1.0 + 85.0*m_nsps/12000.0; // JT9
|
||||
if(m_modeTx=="JT65") txDuration=1.0 + 126*4096/11025.0; // JT65
|
||||
if(m_modeTx=="QRA64") txDuration=1.0 + 84*6912/12000.0; // QRA64
|
||||
if(m_modeTx=="QRA65") { // QRA65
|
||||
if(m_modeTx=="Q65") { // Q65
|
||||
if(m_TRperiod==15) txDuration=0.5 + 85*1800/12000.0;
|
||||
if(m_TRperiod==30) txDuration=0.5 + 85*3600/12000.0;
|
||||
if(m_TRperiod==60) txDuration=1.0 + 85*7680/12000.0;
|
||||
@ -3985,7 +3985,7 @@ void MainWindow::guiUpdate()
|
||||
&m_currentMessageType, 22, 22);
|
||||
if(m_modeTx=="QRA64") genqra64_(message, &ichk, msgsent, const_cast<int *> (itone),
|
||||
&m_currentMessageType, 22, 22);
|
||||
if(m_modeTx=="QRA65") {
|
||||
if(m_modeTx=="Q65") {
|
||||
int ichk65=65;
|
||||
genqra64_(message, &ichk65, msgsent, const_cast<int *> (itone),
|
||||
&m_currentMessageType, 22, 22);
|
||||
@ -4703,7 +4703,7 @@ void MainWindow::processMessage (DecodedText const& message, Qt::KeyboardModifie
|
||||
|| ("JT9" == m_mode && mode != "@")
|
||||
|| ("MSK144" == m_mode && !("&" == mode || "^" == mode))
|
||||
|| ("QRA64" == m_mode && mode.left (1) != ":")) {
|
||||
return; //Currently we do auto-sequencing only in FT4, FT8, MSK144, FST4, and QRA65
|
||||
return; //Currently we do auto-sequencing only in FT4, FT8, MSK144, FST4, and Q65
|
||||
}
|
||||
|
||||
//Skip the rest if no decoded text extracted
|
||||
@ -4811,7 +4811,7 @@ void MainWindow::processMessage (DecodedText const& message, Qt::KeyboardModifie
|
||||
ui->TxFreqSpinBox->setValue(frequency);
|
||||
}
|
||||
if(m_mode != "JT4" && m_mode != "JT65" && !m_mode.startsWith ("JT9") &&
|
||||
m_mode != "QRA64" && m_mode != "QRA65" && m_mode!="FT8" &&
|
||||
m_mode != "QRA64" && m_mode != "Q65" && m_mode!="FT8" &&
|
||||
m_mode!="FT4" && m_mode!="FST4") {
|
||||
return;
|
||||
}
|
||||
@ -6389,13 +6389,13 @@ void MainWindow::on_actionQRA64_triggered()
|
||||
statusChanged();
|
||||
}
|
||||
|
||||
void MainWindow::on_actionQRA65_triggered()
|
||||
void MainWindow::on_actionQ65_triggered()
|
||||
{
|
||||
// on_actionFST4_triggered();
|
||||
m_mode="QRA65";
|
||||
m_modeTx="QRA65";
|
||||
ui->actionQRA65->setChecked(true);
|
||||
switch_mode(Modes::QRA65);
|
||||
m_mode="Q65";
|
||||
m_modeTx="Q65";
|
||||
ui->actionQ65->setChecked(true);
|
||||
switch_mode(Modes::Q65);
|
||||
setup_status_bar(true);
|
||||
m_nsps=6912; //For symspec only
|
||||
m_FFTSize = m_nsps / 2;
|
||||
@ -6411,7 +6411,7 @@ void MainWindow::on_actionQRA65_triggered()
|
||||
m_wideGraph->setTol(ui->sbFtol->value());
|
||||
m_wideGraph->setRxFreq(ui->RxFreqSpinBox->value());
|
||||
m_wideGraph->setTxFreq(ui->TxFreqSpinBox->value());
|
||||
switch_mode (Modes::QRA65);
|
||||
switch_mode (Modes::Q65);
|
||||
// 012345678901234567890123456789012345
|
||||
displayWidgets(nWidgets("111111010110110100010000001100000000"));
|
||||
statusChanged();
|
||||
@ -6464,7 +6464,7 @@ void MainWindow::on_actionMSK144_triggered()
|
||||
if("JT9_JT65"==m_mode) ui->actionJT9_JT65->setChecked(true);
|
||||
if("ISCAT"==m_mode) ui->actionISCAT->setChecked(true);
|
||||
if("QRA64"==m_mode) ui->actionQRA64->setChecked(true);
|
||||
if("QRA65"==m_mode) ui->actionQRA65->setChecked(true);
|
||||
if("Q65"==m_mode) ui->actionQ65->setChecked(true);
|
||||
if("WSPR"==m_mode) ui->actionWSPR->setChecked(true);
|
||||
if("Echo"==m_mode) ui->actionEcho->setChecked(true);
|
||||
if("FreqCal"==m_mode) ui->actionFreqCal->setChecked(true);
|
||||
@ -7312,7 +7312,7 @@ void MainWindow::transmit (double snr)
|
||||
true, false, snr, m_TRperiod);
|
||||
}
|
||||
|
||||
if (m_modeTx == "QRA65") {
|
||||
if (m_modeTx == "Q65") {
|
||||
int nsps=1800;
|
||||
if(m_TRperiod==30) nsps=3600;
|
||||
if(m_TRperiod==60) nsps=7680;
|
||||
@ -7320,7 +7320,7 @@ void MainWindow::transmit (double snr)
|
||||
if(m_TRperiod==300) nsps=41472;
|
||||
int mode65=pow(2.0,double(m_nSubMode));
|
||||
toneSpacing=mode65*12000.0/nsps;
|
||||
Q_EMIT sendMessage (m_mode, NUM_QRA65_SYMBOLS,
|
||||
Q_EMIT sendMessage (m_mode, NUM_Q65_SYMBOLS,
|
||||
double(nsps), ui->TxFreqSpinBox->value () - m_XIT,
|
||||
toneSpacing, m_soundOutput, m_config.audio_output_channel (),
|
||||
true, false, snr, m_TRperiod);
|
||||
@ -7581,9 +7581,9 @@ void::MainWindow::VHF_features_enabled(bool b)
|
||||
void MainWindow::on_sbTR_valueChanged(int value)
|
||||
{
|
||||
// if(!m_bFastMode and n>m_nSubMode) m_MinW=m_nSubMode;
|
||||
if(m_bFastMode or m_mode=="FreqCal" or m_mode=="FST4" or m_mode=="FST4W" or m_mode=="QRA65") {
|
||||
if(m_bFastMode or m_mode=="FreqCal" or m_mode=="FST4" or m_mode=="FST4W" or m_mode=="Q65") {
|
||||
m_TRperiod = value;
|
||||
if (m_mode == "FST4" || m_mode == "FST4W" || m_mode=="QRA65")
|
||||
if (m_mode == "FST4" || m_mode == "FST4W" || m_mode=="Q65")
|
||||
{
|
||||
if (m_TRperiod < 60)
|
||||
{
|
||||
@ -7627,7 +7627,7 @@ void MainWindow::on_sbTR_FST4W_valueChanged(int value)
|
||||
QChar MainWindow::current_submode () const
|
||||
{
|
||||
QChar submode {0};
|
||||
if (m_mode.contains (QRegularExpression {R"(^(JT65|JT9|JT4|ISCAT|QRA64|QRA65)$)"})
|
||||
if (m_mode.contains (QRegularExpression {R"(^(JT65|JT9|JT4|ISCAT|QRA64|Q65)$)"})
|
||||
&& (m_config.enable_VHF_features () || "JT4" == m_mode || "ISCAT" == m_mode))
|
||||
{
|
||||
submode = m_nSubMode + 65;
|
||||
@ -9256,7 +9256,7 @@ void MainWindow::set_mode (QString const& mode)
|
||||
else if ("JT9+JT65" == mode) on_actionJT9_JT65_triggered ();
|
||||
else if ("JT65" == mode) on_actionJT65_triggered ();
|
||||
else if ("QRA64" == mode) on_actionQRA64_triggered ();
|
||||
else if ("QRA65" == mode) on_actionQRA65_triggered ();
|
||||
else if ("Q65" == mode) on_actionQ65_triggered ();
|
||||
else if ("FreqCal" == mode) on_actionFreqCal_triggered ();
|
||||
else if ("ISCAT" == mode) on_actionISCAT_triggered ();
|
||||
else if ("MSK144" == mode) on_actionMSK144_triggered ();
|
||||
|
@ -48,7 +48,7 @@
|
||||
#define NUM_ISCAT_SYMBOLS 1291 //30*11025/256
|
||||
#define NUM_MSK144_SYMBOLS 144 //s8 + d48 + s8 + d80
|
||||
#define NUM_QRA64_SYMBOLS 84 //63 data + 21 sync
|
||||
#define NUM_QRA65_SYMBOLS 85 //63 data + 22 sync
|
||||
#define NUM_Q65_SYMBOLS 85 //63 data + 22 sync
|
||||
#define NUM_FT8_SYMBOLS 79
|
||||
#define NUM_FT4_SYMBOLS 105
|
||||
#define NUM_FST4_SYMBOLS 160 //240/2 data + 5*8 sync
|
||||
@ -301,7 +301,7 @@ private slots:
|
||||
void on_cbCQTx_toggled(bool b);
|
||||
void on_actionMSK144_triggered();
|
||||
void on_actionQRA64_triggered();
|
||||
void on_actionQRA65_triggered();
|
||||
void on_actionQ65_triggered();
|
||||
void on_actionFreqCal_triggered();
|
||||
void splash_done ();
|
||||
void on_measure_check_box_stateChanged (int);
|
||||
|
@ -2895,7 +2895,7 @@ list. The list can be maintained in Settings (F2).</string>
|
||||
<addaction name="actionJT9_JT65"/>
|
||||
<addaction name="actionJT65"/>
|
||||
<addaction name="actionQRA64"/>
|
||||
<addaction name="actionQRA65"/>
|
||||
<addaction name="actionQ65"/>
|
||||
<addaction name="separator"/>
|
||||
<addaction name="actionISCAT"/>
|
||||
<addaction name="actionMSK144"/>
|
||||
@ -3383,12 +3383,12 @@ list. The list can be maintained in Settings (F2).</string>
|
||||
<string>FST4W</string>
|
||||
</property>
|
||||
</action>
|
||||
<action name="actionQRA65">
|
||||
<action name="actionQ65">
|
||||
<property name="checkable">
|
||||
<bool>true</bool>
|
||||
</property>
|
||||
<property name="text">
|
||||
<string>QRA65</string>
|
||||
<string>Q65</string>
|
||||
</property>
|
||||
</action>
|
||||
<action name="actionSWL_Mode">
|
||||
|
@ -471,7 +471,7 @@ void CPlotter::DrawOverlay() //DrawOverlay()
|
||||
if(m_nSubMode==4) bw=16*bw; //E
|
||||
}
|
||||
|
||||
if(m_mode=="QRA65") { //QRA65
|
||||
if(m_mode=="Q65") { //Q65
|
||||
int h=int(pow(2.0,m_nSubMode));
|
||||
int nsps=1800;
|
||||
if(m_TRperiod==30) nsps=3600;
|
||||
@ -512,7 +512,7 @@ void CPlotter::DrawOverlay() //DrawOverlay()
|
||||
int yTxTop=12;
|
||||
int yRxBottom=yTxTop + 2*yh + 4;
|
||||
if(m_mode=="JT9" or m_mode=="JT65" or m_mode=="JT9+JT65"
|
||||
or m_mode=="QRA64" or m_mode=="QRA65" or m_mode=="FT8" or m_mode=="FT4"
|
||||
or m_mode=="QRA64" or m_mode=="Q65" or m_mode=="FT8" or m_mode=="FT4"
|
||||
or m_mode.startsWith("FST4")) {
|
||||
|
||||
if(m_mode=="FST4" and !m_bSingleDecode) {
|
||||
@ -524,7 +524,7 @@ void CPlotter::DrawOverlay() //DrawOverlay()
|
||||
painter0.drawLine(x2,25,x2-5,20);
|
||||
}
|
||||
|
||||
if(m_mode=="QRA64" or m_mode=="QRA65" or (m_mode=="JT65" and m_bVHF)) {
|
||||
if(m_mode=="QRA64" or m_mode=="Q65" or (m_mode=="JT65" and m_bVHF)) {
|
||||
painter0.setPen(penGreen);
|
||||
x1=XfromFreq(m_rxFreq-m_tol);
|
||||
x2=XfromFreq(m_rxFreq+m_tol);
|
||||
@ -562,7 +562,7 @@ void CPlotter::DrawOverlay() //DrawOverlay()
|
||||
}
|
||||
|
||||
if(m_mode=="JT9" or m_mode=="JT65" or m_mode=="JT9+JT65" or
|
||||
m_mode.mid(0,4)=="WSPR" or m_mode=="QRA64" or m_mode=="QRA65" or m_mode=="FT8"
|
||||
m_mode.mid(0,4)=="WSPR" or m_mode=="QRA64" or m_mode=="Q65" or m_mode=="FT8"
|
||||
or m_mode=="FT4" or m_mode.startsWith("FST4")) {
|
||||
painter0.setPen(penRed);
|
||||
x1=XfromFreq(m_txFreq);
|
||||
|
Loading…
Reference in New Issue
Block a user