diff --git a/CMakeLists.txt b/CMakeLists.txt index 99dc533a1..5d39c437d 100644 --- a/CMakeLists.txt +++ b/CMakeLists.txt @@ -360,6 +360,7 @@ set (wsjt_FSRCS lib/jt65_decode.f90 lib/jt65_mod.f90 lib/ft8_decode.f90 + lib/ft4_decode.f90 lib/jt9_decode.f90 lib/options.f90 lib/packjt.f90 @@ -517,9 +518,9 @@ set (wsjt_FSRCS lib/msk144sim.f90 lib/mskrtd.f90 lib/nuttal_window.f90 + lib/ft4/ft4b.f90 lib/ft4/ft4sim.f90 lib/ft4/ft4sim_mult.f90 - lib/ft4/ft4_decode.f90 lib/ft4/ft4_downsample.f90 lib/77bit/my_hash.f90 lib/wsprd/osdwspr.f90 diff --git a/Modulator.cpp b/Modulator.cpp index 8811d16a3..725de9e42 100644 --- a/Modulator.cpp +++ b/Modulator.cpp @@ -92,11 +92,9 @@ void Modulator::start (unsigned symbolsLength, double framesPerSymbol, if (synchronize && !m_tuning && !m_bFastMode) { m_silentFrames = m_ic + m_frameRate / (1000 / delay_ms) - (mstr * (m_frameRate / 1000)); } - if((symbolsLength==103 or symbolsLength==105) and framesPerSymbol==512 + if(symbolsLength==105 and framesPerSymbol==512 and (toneSpacing==12000.0/512.0 or toneSpacing==-2.0)) { //### FT4 parameters - delay_ms=100; - mstr=5000; m_ic=0; m_silentFrames=0; } @@ -159,6 +157,8 @@ qint64 Modulator::readData (char * data, qint64 maxSize) qint16 * end (samples + numFrames * (bytesPerFrame () / sizeof (qint16))); qint64 framesGenerated (0); +// if(m_ic==0) qDebug() << "Modulator::readData" << 0.001*(QDateTime::currentMSecsSinceEpoch() % (1000*m_TRperiod)); + switch (m_state) { case Synchronizing: @@ -180,8 +180,7 @@ qint64 Modulator::readData (char * data, qint64 maxSize) case Active: { unsigned int isym=0; -// qDebug() << "Mod A" << m_toneSpacing << m_frequency << m_nsps -// << m_ic << m_symbolsLength << icw[0]; + if(!m_tuning) isym=m_ic/(4.0*m_nsps); // Actual fsample=48000 bool slowCwId=((isym >= m_symbolsLength) && (icw[0] > 0)) && (!m_bFastMode); if(m_TRperiod==3) slowCwId=false; @@ -192,6 +191,8 @@ qint64 Modulator::readData (char * data, qint64 maxSize) if(m_bFastMode and (icw[0]>0) and (tsec>(m_TRperiod-5.0))) fastCwId=true; if(!m_bFastMode) m_nspd=2560; // 22.5 WPM +// qDebug() << "Mod A" << m_ic << isym << tsec; + if(slowCwId or fastCwId) { // Transmit CW ID? m_dphi = m_twoPi*m_frequency/m_frameRate; if(m_bFastMode and !bCwId) { @@ -263,10 +264,10 @@ qint64 Modulator::readData (char * data, qint64 maxSize) } qint16 sample; + for (unsigned i = 0; i < numFrames && m_ic <= i1; ++i) { isym=0; - if(!m_tuning and m_TRperiod!=3) isym=m_ic / (4.0 * m_nsps); //Actual - //fsample=48000 + if(!m_tuning and m_TRperiod!=3) isym=m_ic/(4.0*m_nsps); //Actual fsample=48000 if(m_bFastMode) isym=isym%m_symbolsLength; if (isym != m_isym0 || m_frequency != m_frequency0) { if(itone[0]>=100) { @@ -278,8 +279,6 @@ qint64 Modulator::readData (char * data, qint64 maxSize) m_toneFrequency0=m_frequency + itone[isym]*m_toneSpacing; } } -// qDebug() << "Mod B" << m_bFastMode << m_ic << numFrames << isym << itone[isym] -// << m_toneFrequency0 << m_nsps; m_dphi = m_twoPi * m_toneFrequency0 / m_frameRate; m_isym0 = isym; m_frequency0 = m_frequency; //??? @@ -302,10 +301,10 @@ qint64 Modulator::readData (char * data, qint64 maxSize) sample=qRound(m_amp*qSin(m_phi)); //Here's where we transmit from a precomputed wave[] array: - if(!m_tuning and (m_toneSpacing < 0)) sample=qRound(m_amp*foxcom_.wave[m_ic]); -// if(m_ic < 10) qDebug() << "Mod Tx" << m_ic << m_amp -// << foxcom_.wave[m_ic] << sample -// << m_toneSpacing; + if(!m_tuning and (m_toneSpacing < 0)) { + m_amp=32767.0; + sample=qRound(m_amp*foxcom_.wave[m_ic]); + } samples = load(postProcessSample(sample), samples); ++framesGenerated; @@ -322,9 +321,9 @@ qint64 Modulator::readData (char * data, qint64 maxSize) } m_frequency0 = m_frequency; - // done for this chunk - continue on next call -// qint64 ms1=QDateTime::currentMSecsSinceEpoch() - m_ms0; -// if(m_ic>=4*144*160) qDebug() << "Modulator finished" << m_ic << 0.001*ms1; +// done for this chunk - continue on next call + +// qDebug() << "Mod B" << m_ic << i1 << 0.001*(QDateTime::currentMSecsSinceEpoch() % (1000*m_TRperiod)); while (samples != end) // pad block with silence { diff --git a/lib/decoder.f90 b/lib/decoder.f90 index 218a6cbf7..37ca5b1bd 100644 --- a/lib/decoder.f90 +++ b/lib/decoder.f90 @@ -7,6 +7,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample) use jt65_decode use jt9_decode use ft8_decode + use ft4_decode include 'jt9com.f90' include 'timer_common.inc' @@ -27,6 +28,10 @@ subroutine multimode_decoder(ss,id2,params,nfsample) integer :: decoded end type counting_ft8_decoder + type, extends(ft4_decoder) :: counting_ft4_decoder + integer :: decoded + end type counting_ft4_decoder + real ss(184,NSMAX) logical baddata,newdat65,newdat9,single_decode,bVHF,bad0,newdat,ex integer*2 id2(NTMAX*12000) @@ -40,6 +45,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample) type(counting_jt65_decoder) :: my_jt65 type(counting_jt9_decoder) :: my_jt9 type(counting_ft8_decoder) :: my_ft8 + type(counting_ft4_decoder) :: my_ft4 !cast C character arrays to Fortran character strings datetime=transfer(params%datetime, datetime) @@ -53,6 +59,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample) my_jt65%decoded = 0 my_jt9%decoded = 0 my_ft8%decoded = 0 + my_ft4%decoded = 0 single_decode=iand(params%nexp_decode,32).ne.0 bVHF=iand(params%nexp_decode,64).ne.0 @@ -142,6 +149,15 @@ subroutine multimode_decoder(ss,id2,params,nfsample) go to 800 endif + if(params%nmode.eq.5) then + call timer('decft4 ',0) + call my_ft4%decode(ft4_decoded,id2,params%nQSOProgress,params%nfqso, & + params%nutc,params%nfa,params%nfb,params%ndepth,ncontest, & + mycall,hiscall) + call timer('decft4 ',1) + go to 800 + endif + rms=sqrt(dot_product(float(id2(300000:310000)), & float(id2(300000:310000)))/10000.0) if(rms.lt.2.0) go to 800 @@ -258,7 +274,8 @@ subroutine multimode_decoder(ss,id2,params,nfsample) !$omp end parallel sections ! JT65 is not yet producing info for nsynced, ndecoded. -800 ndecoded = my_jt4%decoded + my_jt65%decoded + my_jt9%decoded + my_ft8%decoded +800 ndecoded = my_jt4%decoded + my_jt65%decoded + my_jt9%decoded + & + my_ft8%decoded + my_ft4%decoded write(*,1010) nsynced,ndecoded 1010 format('',2i4) call flush(6) @@ -561,4 +578,44 @@ contains return end subroutine ft8_decoded + subroutine ft4_decoded (this,sync,snr,dt,freq,decoded,nap,qual) + use ft4_decode + implicit none + + class(ft4_decoder), intent(inout) :: this + real, intent(in) :: sync + integer, intent(in) :: snr + real, intent(in) :: dt + real, intent(in) :: freq + character(len=37), intent(in) :: decoded + character c1*12,c2*12,g2*4,w*4 + integer i0,i1,i2,i3,i4,i5,n30,nwrap + integer, intent(in) :: nap + real, intent(in) :: qual + character*2 annot + character*37 decoded0 + + decoded0=decoded + + annot=' ' + if(ncontest.eq.0 .and. nap.ne.0) then + write(annot,'(a1,i1)') 'a',nap + if(qual.lt.0.17) decoded0(37:37)='?' + endif + + write(*,1001) params%nutc,snr,dt,nint(freq),decoded0,annot +1001 format(i6.6,i4,f5.1,i5,' ~ ',1x,a37,1x,a2) + write(13,1002) params%nutc,nint(sync),snr,dt,freq,0,decoded0 +1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a37,' FT8') + + call flush(6) + call flush(13) + + select type(this) + type is (counting_ft4_decoder) + this%decoded = this%decoded + 1 + end select + + return + end subroutine ft4_decoded end subroutine multimode_decoder diff --git a/lib/ft4/ft4b.f90 b/lib/ft4/ft4b.f90 new file mode 100644 index 000000000..d425277ef --- /dev/null +++ b/lib/ft4/ft4b.f90 @@ -0,0 +1,489 @@ +subroutine ft4b(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & + iwave,ndecodes,mycall,hiscall,cqstr,line,data_dir) + + use packjt77 + include 'ft4_params.f90' + parameter (NSS=NSPS/NDOWN) + + character message*37,msgsent*37,msg0*37 + character c77*77 + character*61 line,linex(100) + character*37 decodes(100) + character*512 data_dir,fname + character*17 cdatetime0 + character*12 mycall,hiscall + character*12 mycall0,hiscall0 + character*6 hhmmss + character*4 cqstr,cqstr0 + + complex cd2(0:NMAX/NDOWN-1) !Complex waveform + complex cb(0:NMAX/NDOWN-1) + complex cd(0:NN*NSS-1) !Complex waveform + complex ctwk(2*NSS),ctwk2(2*NSS,-16:16) + complex csymb(NSS) + complex cs(0:3,NN) + real s4(0:3,NN) + + real bmeta(2*NN),bmetb(2*NN),bmetc(2*NN) + real a(5) + real llr(2*ND),llra(2*ND),llrb(2*ND),llrc(2*ND),llrd(2*ND) + real s2(0:255) + real candidate(3,100) + real savg(NH1),sbase(NH1) + + integer apbits(2*ND) + integer apmy_ru(28),aphis_fd(28) + integer icos4a(0:3),icos4b(0:3),icos4c(0:3),icos4d(0:3) + integer*2 iwave(NMAX) !Raw received data + integer*1 message77(77),rvec(77),apmask(2*ND),cw(2*ND) + integer*1 hbits(2*NN) + integer graymap(0:3) + integer ip(1) + integer nappasses(0:5) ! # of decoding passes for QSO States 0-5 + integer naptypes(0:5,4) ! nQSOProgress, decoding pass + integer mcq(29) + integer mrrr(19),m73(19),mrr73(19) + + logical nohiscall,unpk77_success + logical one(0:255,0:7) ! 256 4-symbol sequences, 8 bits + logical first, dobigfft + + data icos4a/0,1,3,2/ + data icos4b/1,0,2,3/ + data icos4c/2,3,1,0/ + data icos4d/3,2,0,1/ + data graymap/0,1,3,2/ + data msg0/' '/ + data first/.true./ + data mcq/0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,0,0/ + data mrrr/0,1,1,1,1,1,1,0,1,0,0,1,0,0,1,0,0,0,1/ + data m73/0,1,1,1,1,1,1,0,1,0,0,1,0,1,0,0,0,0,1/ + data mrr73/0,1,1,1,1,1,1,0,0,1,1,1,0,1,0,1,0,0,1/ + data rvec/0,1,0,0,1,0,1,0,0,1,0,1,1,1,1,0,1,0,0,0,1,0,0,1,1,0,1,1,0, & + 1,0,0,1,0,1,1,0,0,0,0,1,0,0,0,1,0,1,0,0,1,1,1,1,0,0,1,0,1, & + 0,1,0,1,0,1,1,0,1,1,1,1,1,0,0,0,1,0,1/ + save fs,dt,tt,txt,twopi,h,one,first,linex,apbits,nappasses,naptypes, & + mycall0,hiscall0,msg0,cqstr0,ctwk2 + + call clockit('ft4_deco',0) + hhmmss=cdatetime0(8:13) + + if(first) then + fs=12000.0/NDOWN !Sample rate after downsampling + dt=1/fs !Sample interval after downsample (s) + tt=NSPS*dt !Duration of "itone" symbols (s) + txt=NZ*dt !Transmission length (s) without ramp up/down + twopi=8.0*atan(1.0) + h=1.0 + one=.false. + do i=0,255 + do j=0,7 + if(iand(i,2**j).ne.0) one(i,j)=.true. + enddo + enddo + + do idf=-16,16 + a=0. + a(1)=real(idf) + ctwk=1. + call clockit('twkfreq1',0) + call twkfreq1(ctwk,2*NSS,fs/2.0,a,ctwk2(:,idf)) + call clockit('twkfreq1',1) + enddo + + mrrr=2*mod(mrrr+rvec(59:77),2)-1 + m73=2*mod(m73+rvec(59:77),2)-1 + mrr73=2*mod(mrr73+rvec(59:77),2)-1 + nappasses(0)=2 + nappasses(1)=2 + nappasses(2)=2 + nappasses(3)=2 + nappasses(4)=2 + nappasses(5)=3 + +! iaptype +!------------------------ +! 1 CQ ??? ??? (29 ap bits) +! 2 MyCall ??? ??? (29 ap bits) +! 3 MyCall DxCall ??? (58 ap bits) +! 4 MyCall DxCall RRR (77 ap bits) +! 5 MyCall DxCall 73 (77 ap bits) +! 6 MyCall DxCall RR73 (77 ap bits) +!******** + naptypes(0,1:4)=(/1,2,0,0/) ! Tx6 selected (CQ) + naptypes(1,1:4)=(/2,3,0,0/) ! Tx1 + naptypes(2,1:4)=(/2,3,0,0/) ! Tx2 + naptypes(3,1:4)=(/3,6,0,0/) ! Tx3 + naptypes(4,1:4)=(/3,6,0,0/) ! Tx4 + naptypes(5,1:4)=(/3,1,2,0/) ! Tx5 + + mycall0='' + hiscall0='' + cqstr0='' + first=.false. + endif + + if(cqstr.ne.cqstr0) then + i0=index(cqstr,' ') + if(i0.le.1) then + message='CQ A1AA AA01' + else + message='CQ '//cqstr(1:i0-1)//' A1AA AA01' + endif + i3=-1 + n3=-1 + call pack77(message,i3,n3,c77) + call unpack77(c77,1,msgsent,unpk77_success) + read(c77,'(29i1)') mcq + mcq=2*mod(mcq+rvec(1:29),2)-1 + cqstr0=cqstr + endif + + l1=index(mycall,char(0)) + if(l1.ne.0) mycall(l1:)=" " + l1=index(hiscall,char(0)) + if(l1.ne.0) hiscall(l1:)=" " + if(mycall.ne.mycall0 .or. hiscall.ne.hiscall0) then + apbits=0 + apbits(1)=99 + apbits(30)=99 + apmy_ru=0 + aphis_fd=0 + + if(len(trim(mycall)) .lt. 3) go to 10 + + nohiscall=.false. + hiscall0=hiscall + if(len(trim(hiscall0)).lt.3) then + hiscall0=mycall ! use mycall for dummy hiscall - mycall won't be hashed. + nohiscall=.true. + endif + message=trim(mycall)//' '//trim(hiscall0)//' RR73' + i3=-1 + n3=-1 + call pack77(message,i3,n3,c77) + call unpack77(c77,1,msgsent,unpk77_success) + if(i3.ne.1 .or. (message.ne.msgsent) .or. .not.unpk77_success) go to 10 + read(c77,'(77i1)') message77 + apmy_ru=2*mod(message77(1:28)+rvec(2:29),2)-1 + aphis_fd=2*mod(message77(30:57)+rvec(29:56),2)-1 + message77=mod(message77+rvec,2) + call encode174_91(message77,cw) + apbits=2*cw-1 + if(nohiscall) apbits(30)=99 + +10 continue + mycall0=mycall + hiscall0=hiscall + endif + candidate=0.0 + ncand=0 + syncmin=1.2 + maxcand=100 + + fa=nfa + fb=nfb + call clockit('getcand4',0) + call getcandidates4(iwave,fa,fb,syncmin,nfqso,maxcand,savg,candidate, & + ncand,sbase) + call clockit('getcand4',1) + + ndecodes=0 + dobigfft=.true. + do icand=1,ncand + f0=candidate(1,icand) + snr=candidate(3,icand)-1.0 + if( f0.le.10.0 .or. f0.ge.4990.0 ) cycle + call clockit('ft4_down',0) + call ft4_downsample(iwave,dobigfft,f0,cd2) !Downsample from 512 to 32 Sa/Symbol + if(dobigfft) dobigfft=.false. + call clockit('ft4_down',1) + + sum2=sum(cd2*conjg(cd2))/(real(NMAX)/real(NDOWN)) + if(sum2.gt.0.0) cd2=cd2/sqrt(sum2) +! Sample rate is now 12000/16 = 750 samples/second + do isync=1,2 + if(isync.eq.1) then + idfmin=-12 + idfmax=12 + idfstp=3 + ibmin=0 + ibmax=216 !Max DT = 216/750 = 0.288 s + ibstp=4 + else + idfmin=idfbest-4 + idfmax=idfbest+4 + idfstp=1 + ibmin=max(0,ibest-5) + ibmax=min(ibest+5,NMAX/NDOWN-1) + ibstp=1 + endif + ibest=-1 + smax=-99. + idfbest=0 + do idf=idfmin,idfmax,idfstp + + call clockit('sync4d ',0) + do istart=ibmin,ibmax,ibstp + call sync4d(cd2,istart,ctwk2(:,idf),1,sync) !Find sync power + if(sync.gt.smax) then + smax=sync + ibest=istart + idfbest=idf + endif + enddo + call clockit('sync4d ',1) + + enddo + enddo + f0=f0+real(idfbest) + if( f0.le.10.0 .or. f0.ge.4990.0 ) cycle + + call clockit('ft4down ',0) + call ft4_downsample(iwave,dobigfft,f0,cb) !Final downsample with corrected f0 + call clockit('ft4down ',1) + sum2=sum(abs(cb)**2)/(real(NSS)*NN) + if(sum2.gt.0.0) cb=cb/sqrt(sum2) + cd=cb(ibest:ibest+NN*NSS-1) + call clockit('four2a ',0) + do k=1,NN + i1=(k-1)*NSS + csymb=cd(i1:i1+NSS-1) + call four2a(csymb,NSS,1,-1,1) + cs(0:3,k)=csymb(1:4) + s4(0:3,k)=abs(csymb(1:4)) + enddo + call clockit('four2a ',1) + +! Sync quality check + is1=0 + is2=0 + is3=0 + is4=0 + do k=1,4 + ip=maxloc(s4(:,k)) + if(icos4a(k-1).eq.(ip(1)-1)) is1=is1+1 + ip=maxloc(s4(:,k+33)) + if(icos4b(k-1).eq.(ip(1)-1)) is2=is2+1 + ip=maxloc(s4(:,k+66)) + if(icos4c(k-1).eq.(ip(1)-1)) is3=is3+1 + ip=maxloc(s4(:,k+99)) + if(icos4d(k-1).eq.(ip(1)-1)) is4=is4+1 + enddo + nsync=is1+is2+is3+is4 !Number of correct hard sync symbols, 0-16 + if(smax .lt. 0.7 .or. nsync .lt. 8) cycle + + do nseq=1,3 !Try coherent sequences of 1, 2, and 4 symbols + if(nseq.eq.1) nsym=1 + if(nseq.eq.2) nsym=2 + if(nseq.eq.3) nsym=4 + nt=2**(2*nsym) + do ks=1,NN-nsym+1,nsym !87+16=103 symbols. + amax=-1.0 + do i=0,nt-1 + i1=i/64 + i2=iand(i,63)/16 + i3=iand(i,15)/4 + i4=iand(i,3) + if(nsym.eq.1) then + s2(i)=abs(cs(graymap(i4),ks)) + elseif(nsym.eq.2) then + s2(i)=abs(cs(graymap(i3),ks)+cs(graymap(i4),ks+1)) + elseif(nsym.eq.4) then + s2(i)=abs(cs(graymap(i1),ks ) + & + cs(graymap(i2),ks+1) + & + cs(graymap(i3),ks+2) + & + cs(graymap(i4),ks+3) & + ) + else + print*,"Error - nsym must be 1, 2, or 4." + endif + enddo + ipt=1+(ks-1)*2 + if(nsym.eq.1) ibmax=1 + if(nsym.eq.2) ibmax=3 + if(nsym.eq.4) ibmax=7 + do ib=0,ibmax + bm=maxval(s2(0:nt-1),one(0:nt-1,ibmax-ib)) - & + maxval(s2(0:nt-1),.not.one(0:nt-1,ibmax-ib)) + if(ipt+ib.gt.2*NN) cycle + if(nsym.eq.1) then + bmeta(ipt+ib)=bm + elseif(nsym.eq.2) then + bmetb(ipt+ib)=bm + elseif(nsym.eq.4) then + bmetc(ipt+ib)=bm + endif + enddo + enddo + enddo + + bmetb(205:206)=bmeta(205:206) + bmetc(201:204)=bmetb(201:204) + bmetc(205:206)=bmeta(205:206) + + call clockit('normaliz',0) + call normalizebmet(bmeta,2*NN) + call normalizebmet(bmetb,2*NN) + call normalizebmet(bmetc,2*NN) + call clockit('normaliz',1) + + hbits=0 + where(bmeta.ge.0) hbits=1 + ns1=count(hbits( 1: 8).eq.(/0,0,0,1,1,0,1,1/)) + ns2=count(hbits( 67: 74).eq.(/0,1,0,0,1,1,1,0/)) + ns3=count(hbits(133:140).eq.(/1,1,1,0,0,1,0,0/)) + ns4=count(hbits(199:206).eq.(/1,0,1,1,0,0,0,1/)) + nsync_qual=ns1+ns2+ns3+ns4 + if(nsync_qual.lt. 20) cycle + + scalefac=2.83 + llra( 1: 58)=bmeta( 9: 66) + llra( 59:116)=bmeta( 75:132) + llra(117:174)=bmeta(141:198) + llra=scalefac*llra + llrb( 1: 58)=bmetb( 9: 66) + llrb( 59:116)=bmetb( 75:132) + llrb(117:174)=bmetb(141:198) + llrb=scalefac*llrb + llrc( 1: 58)=bmetc( 9: 66) + llrc( 59:116)=bmetc( 75:132) + llrc(117:174)=bmetc(141:198) + llrc=scalefac*llrc + + apmag=maxval(abs(llra))*1.1 + npasses=3+nappasses(nQSOProgress) + if(ncontest.ge.5) npasses=3 ! Don't support Fox and Hound + do ipass=1,npasses + if(ipass.eq.1) llr=llra + if(ipass.eq.2) llr=llrb + if(ipass.eq.3) llr=llrc + if(ipass.le.3) then + apmask=0 + iaptype=0 + endif + + if(ipass .gt. 3) then + llrd=llrc + iaptype=naptypes(nQSOProgress,ipass-3) + +! ncontest=0 : NONE +! 1 : NA_VHF +! 2 : EU_VHF +! 3 : FIELD DAY +! 4 : RTTY +! 5 : FOX +! 6 : HOUND +! +! Conditions that cause us to bail out of AP decoding + napwid=50 + if(ncontest.le.4 .and. iaptype.ge.3 .and. (abs(f0-nfqso).gt.napwid) ) cycle + if(iaptype.ge.2 .and. apbits(1).gt.1) cycle ! No, or nonstandard, mycall + if(iaptype.ge.3 .and. apbits(30).gt.1) cycle ! No, or nonstandard, dxcall + + if(iaptype.eq.1) then ! CQ or CQ TEST or CQ FD or CQ RU or CQ SCC + apmask=0 + apmask(1:29)=1 + llrd(1:29)=apmag*mcq(1:29) + endif + + if(iaptype.eq.2) then ! MyCall,???,??? + apmask=0 + if(ncontest.eq.0.or.ncontest.eq.1) then + apmask(1:29)=1 + llrd(1:29)=apmag*apbits(1:29) + else if(ncontest.eq.2) then + apmask(1:28)=1 + llrd(1:28)=apmag*apbits(1:28) + else if(ncontest.eq.3) then + apmask(1:28)=1 + llrd(1:28)=apmag*apbits(1:28) + else if(ncontest.eq.4) then + apmask(2:29)=1 + llrd(2:29)=apmag*apmy_ru(1:28) + endif + endif + + if(iaptype.eq.3) then ! MyCall,DxCall,??? + apmask=0 + if(ncontest.eq.0.or.ncontest.eq.1.or.ncontest.eq.2) then + apmask(1:58)=1 + llrd(1:58)=apmag*apbits(1:58) + else if(ncontest.eq.3) then ! Field Day + apmask(1:56)=1 + llrd(1:28)=apmag*apbits(1:28) + llrd(29:56)=apmag*aphis_fd(1:28) + else if(ncontest.eq.4) then ! RTTY RU + apmask(2:57)=1 + llrd(2:29)=apmag*apmy_ru(1:28) + llrd(30:57)=apmag*apbits(30:57) + endif + endif + + if(iaptype.eq.4 .or. iaptype.eq.5 .or. iaptype.eq.6) then + apmask=0 + if(ncontest.le.4) then + apmask(1:91)=1 ! mycall, hiscall, RRR|73|RR73 + if(iaptype.eq.6) llrd(1:91)=apmag*apbits(1:91) + endif + endif + + llr=llrd + endif + max_iterations=40 + message77=0 + call clockit('bpdecode',0) + call bpdecode174_91(llr,apmask,max_iterations,message77, & + cw,nharderror,niterations) + call clockit('bpdecode',1) + if(sum(message77).eq.0) cycle + if( nharderror.ge.0 ) then + message77=mod(message77+rvec,2) ! remove rvec scrambling + write(c77,'(77i1)') message77(1:77) + call unpack77(c77,1,message,unpk77_success) + idupe=0 + do i=1,ndecodes + if(decodes(i).eq.message) idupe=1 + enddo + if(ibest.le.10 .and. message.eq.msg0) idupe=1 !Already decoded + if(idupe.eq.1) exit + ndecodes=ndecodes+1 + decodes(ndecodes)=message + if(snr.gt.0.0) then + xsnr=10*log10(snr)-14.0 + else + xsnr=-20.0 + endif + nsnr=nint(max(-20.0,xsnr)) + freq=f0 + tsig=mod(tbuf + ibest/750.0,100.0) + + write(line,1000) hhmmss,nsnr,tsig,nint(freq),message +1000 format(a6,i4,f5.1,i5,' + ',1x,a37) + l1=index(data_dir,char(0))-1 + if(l1.ge.1) data_dir(l1+1:l1+1)="/" + fname=data_dir(1:l1+1)//'all_ft4.txt' + open(24,file=trim(fname),status='unknown',position='append') + write(24,1002) cdatetime0,nsnr,tsig,nint(freq),message, & + nharderror,nsync_qual,ipass,niterations,iaptype,nsync + if(hhmmss.eq.' ') write(*,1002) cdatetime0,nsnr, & + tsig,nint(freq),message,nharderror,nsync_qual,ipass, & + niterations,iaptype +1002 format(a17,i4,f5.1,i5,' Rx ',a37,6i4) + close(24) + linex(ndecodes)=line + if(ibest.ge.ibmax-15) msg0=message !Possible dupe candidate + exit + endif + enddo !Sequence estimation + enddo !Candidate list + call clockit('ft4_deco',1) + call clockit2(data_dir) + call clockit('ft4_deco',101) + return + + entry get_ft4msg(idecode,line) + line=linex(idecode) + return + + end subroutine ft4b diff --git a/lib/ft4/ft4d.f90 b/lib/ft4/ft4d.f90 index fa7c8045a..a63e3e0a6 100644 --- a/lib/ft4/ft4d.f90 +++ b/lib/ft4/ft4d.f90 @@ -67,7 +67,7 @@ program ft4d do n=1,nsteps i0=(n-1)*istep + 1 tbuf=(i0-1)/12000.0 - call ft4_decode(cdatetime,tbuf,nfa,nfb,nQSOProgress,ncontest, & + call ft4b(cdatetime,tbuf,nfa,nfb,nQSOProgress,ncontest, & nfqso,iwave(i0),ndecodes,mycall,hiscall,cqstr,line,data_dir) do idecode=1,ndecodes call get_ft4msg(idecode,line) diff --git a/lib/ft4/ft4sim.f90 b/lib/ft4/ft4sim.f90 index 1481840c8..6b5d01599 100644 --- a/lib/ft4/ft4sim.f90 +++ b/lib/ft4/ft4sim.f90 @@ -6,18 +6,19 @@ program ft4sim use packjt77 include 'ft4_params.f90' !Set various constants parameter (NWAVE=NN*NSPS) + parameter (NZZ=18*3456) !62208 type(hdr) h !Header for .wav file character arg*12,fname*17 character msg37*37,msgsent37*37 character c77*77 - complex c0(0:NMAX-1) - complex c(0:NMAX-1) - real wave(NMAX) - real dphi(0:NMAX-1) + complex c0(0:NZZ-1) + complex c(0:NZZ-1) + real wave(NZZ) + real dphi(0:NZZ-1) real pulse(3*NSPS) integer itone(NN) integer*1 msgbits(77) - integer*2 iwave(NMAX) !Generated full-length waveform + integer*2 iwave(NZZ) !Generated full-length waveform integer icos4(4) data icos4/0,1,3,2/ @@ -100,7 +101,8 @@ program ft4sim phi=0.0 c0=0.0 dphi=dphi+twopi*f0*dt - do j=0,NMAX-1 +! do j=0,NMAX-1 !### ??? ### + do j=0,(NN+2)*NSPS-1 c0(j)=cmplx(cos(phi),sin(phi)) phi=mod(phi+dphi(j),twopi) enddo @@ -109,22 +111,19 @@ program ft4sim c0((NN+1)*NSPS:(NN+2)*NSPS-1)=c0((NN+1)*NSPS:(NN+2)*NSPS-1)*(1.0+cos(twopi*(/(i,i=0,NSPS-1)/)/(2.0*NSPS) ))/2.0 c0((NN+2)*NSPS:)=0. - k=nint((xdt+0.14)/dt) + k=nint((xdt+0.5)/dt) c0=cshift(c0,-k) - ia=k do ifile=1,nfiles c=c0 - if(fspread.ne.0.0 .or. delay.ne.0.0) call watterson(c,NMAX,NWAVE,fs,delay,fspread) + if(fspread.ne.0.0 .or. delay.ne.0.0) call watterson(c,NZZ,NWAVE,fs,delay,fspread) c=sig*c - - ib=k wave=real(c) - peak=maxval(abs(wave(ia:ib))) + peak=maxval(abs(wave)) nslots=1 if(snrdb.lt.90) then - do i=1,NMAX !Add gaussian noise at specified SNR + do i=1,NZZ !Add gaussian noise at specified SNR xnoise=gran() wave(i)=wave(i) + xnoise enddo @@ -140,15 +139,14 @@ program ft4sim endif if(any(abs(wave).gt.32767.0)) print*,"Warning - data will be clipped." iwave=nint(wave) - h=default_header(12000,NMAX+2208) + h=default_header(12000,NZZ) write(fname,1102) ifile 1102 format('000000_',i6.6,'.wav') open(10,file=fname,status='unknown',access='stream') write(10) h,iwave !Save to *.wav file - iwave(1:2208)=0 - write(10) iwave(1:2208) !Add 0.5 s of zeroes close(10) write(*,1110) ifile,xdt,f0,snrdb,fname 1110 format(i4,f7.2,f8.2,f7.1,2x,a17) - enddo + enddo + 999 end program ft4sim diff --git a/lib/ft4/ft4sim_mult.f90 b/lib/ft4/ft4sim_mult.f90 index bc696e814..065b2a76b 100644 --- a/lib/ft4/ft4sim_mult.f90 +++ b/lib/ft4/ft4sim_mult.f90 @@ -6,7 +6,7 @@ program ft4sim_mult use packjt77 include 'ft4_params.f90' !FT4 protocol constants parameter (NWAVE=NN*NSPS) - parameter (NZZ=15*12000) !Length of .wav file, 180,000 i*2 samples + parameter (NZZ=65760) !Length of .wav file (4.48+1.0)*12000 type(hdr) h !Header for .wav file character arg*12,fname*17,cjunk*4 character msg37*37,msgsent37*37,c77*77 @@ -26,20 +26,19 @@ program ft4sim_mult go to 999 endif call getarg(1,arg) - read(arg,*) nsigs !Number of signals + read(arg,*) nsigs !Number of signals call getarg(2,arg) - read(arg,*) nfiles !Number of files + read(arg,*) nfiles !Number of files twopi=8.0*atan(1.0) - fs=12000.0 !Sample rate (Hz) - dt=1.0/fs !Sample interval (s) - hmod=1.0 !Modulation index (0.5 is MSK, 1.0 is FSK) - tt=NSPS*dt !Duration of unsmoothed symbols (s) - baud=1.0/tt !Keying rate (baud) - txt=NZ*dt !Transmission length (s) without ramp up/down + fs=12000.0 !Sample rate (Hz) + dt=1.0/fs !Sample interval (s) + hmod=1.0 !Modulation index (0.5 is MSK, 1.0 is FSK) + tt=NSPS*dt !Duration of unsmoothed symbols (s) + baud=1.0/tt !Keying rate (baud) + txt=NZ*dt !Transmission length (s) without ramp up/down bandwidth_ratio=2500.0/(fs/2.0) txt=NN*NSPS/12000.0 - xdtmax=10.0 - 0.086 open(10,file='messages.txt',status='old',err=998) do ifile=1,nfiles @@ -57,7 +56,7 @@ program ft4sim_mult if(isnr.lt.-16) isnr=-16 f0=ifreq*93.75/50.0 call random_number(r) - xdt=r*xdtmax + xdt=r-0.5 ! Source-encode, then get itone() i3=-1 n3=-1 @@ -66,7 +65,7 @@ program ft4sim_mult nwave0=(NN+2)*NSPS call gen_ft4wave(itone,NN,NSPS,12000.0,f0,wave0,nwave0) - k0=nint(xdt/dt) + k0=nint((xdt+0.5)/dt) if(k0.lt.1) k0=1 tmp(:k0-1)=0.0 tmp(k0:k0+nwave0-1)=wave0 diff --git a/lib/ft4/ft4_decode.f90 b/lib/ft4_decode.f90 similarity index 84% rename from lib/ft4/ft4_decode.f90 rename to lib/ft4_decode.f90 index 83287e1e9..500cdd081 100644 --- a/lib/ft4/ft4_decode.f90 +++ b/lib/ft4_decode.f90 @@ -1,13 +1,39 @@ -subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & - iwave,ndecodes,mycall,hiscall,cqstr,line,data_dir) +module ft4_decode + + type :: ft4_decoder + procedure(ft4_decode_callback), pointer :: callback + contains + procedure :: decode + end type ft4_decoder - use packjt77 - include 'ft4_params.f90' - parameter (NSS=NSPS/NDOWN) + abstract interface + subroutine ft4_decode_callback (this,sync,snr,dt,freq,decoded,nap,qual) + import ft4_decoder + implicit none + class(ft4_decoder), intent(inout) :: this + real, intent(in) :: sync + integer, intent(in) :: snr + real, intent(in) :: dt + real, intent(in) :: freq + character(len=37), intent(in) :: decoded + integer, intent(in) :: nap + real, intent(in) :: qual + end subroutine ft4_decode_callback + end interface +contains + + subroutine decode(this,callback,iwave,nQSOProgress,nfqso, & + nutc,nfa,nfb,ndepth,ncontest,mycall,hiscall) + use timer_module, only: timer + use packjt77 + include 'ft4/ft4_params.f90' + class(ft4_decoder), intent(inout) :: this + procedure(ft4_decode_callback) :: callback + parameter (NSS=NSPS/NDOWN) + parameter (NZZ=18*3456) character message*37,msgsent*37,msg0*37 character c77*77 - character*61 line,linex(100) character*37 decodes(100) character*512 data_dir,fname character*17 cdatetime0 @@ -16,8 +42,8 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & character*6 hhmmss character*4 cqstr,cqstr0 - complex cd2(0:NMAX/NDOWN-1) !Complex waveform - complex cb(0:NMAX/NDOWN-1) + complex cd2(0:NZZ/NDOWN-1) !Complex waveform + complex cb(0:NZZ/NDOWN-1+NN*NSS) complex cd(0:NN*NSS-1) !Complex waveform complex ctwk(2*NSS),ctwk2(2*NSS,-16:16) complex csymb(NSS) @@ -34,7 +60,7 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & integer apbits(2*ND) integer apmy_ru(28),aphis_fd(28) integer icos4a(0:3),icos4b(0:3),icos4c(0:3),icos4d(0:3) - integer*2 iwave(NMAX) !Raw received data + integer*2 iwave(NZZ) !Raw received data integer*1 message77(77),rvec(77),apmask(2*ND),cw(2*ND) integer*1 hbits(2*NN) integer graymap(0:3) @@ -62,12 +88,11 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & data rvec/0,1,0,0,1,0,1,0,0,1,0,1,1,1,1,0,1,0,0,0,1,0,0,1,1,0,1,1,0, & 1,0,0,1,0,1,1,0,0,0,0,1,0,0,0,1,0,1,0,0,1,1,1,1,0,0,1,0,1, & 0,1,0,1,0,1,1,0,1,1,1,1,1,0,0,0,1,0,1/ - save fs,dt,tt,txt,twopi,h,one,first,linex,apbits,nappasses,naptypes, & + save fs,dt,tt,txt,twopi,h,one,first,apbits,nappasses,naptypes, & mycall0,hiscall0,msg0,cqstr0,ctwk2 - - call clockit('ft4_deco',0) - hhmmss=cdatetime0(8:13) + this%callback => callback + hhmmss=cdatetime0(8:13) if(first) then fs=12000.0/NDOWN !Sample rate after downsampling dt=1/fs !Sample interval after downsample (s) @@ -86,9 +111,7 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & a=0. a(1)=real(idf) ctwk=1. - call clockit('twkfreq1',0) call twkfreq1(ctwk,2*NSS,fs/2.0,a,ctwk2(:,idf)) - call clockit('twkfreq1',1) enddo mrrr=2*mod(mrrr+rvec(59:77),2)-1 @@ -183,23 +206,21 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & fa=nfa fb=nfb - call clockit('getcand4',0) + call timer('getcand4',0) call getcandidates4(iwave,fa,fb,syncmin,nfqso,maxcand,savg,candidate, & ncand,sbase) - call clockit('getcand4',1) + call timer('getcand4',1) ndecodes=0 dobigfft=.true. do icand=1,ncand f0=candidate(1,icand) snr=candidate(3,icand)-1.0 - if( f0.le.10.0 .or. f0.ge.4990.0 ) cycle - call clockit('ft4_down',0) - call ft4_downsample(iwave,dobigfft,f0,cd2) !Downsample from 512 to 32 Sa/Symbol + call timer('ft4_down',0) + call ft4_downsample(iwave,dobigfft,f0,cd2) !Downsample to 32 Sam/Sym + call timer('ft4_down',1) if(dobigfft) dobigfft=.false. - call clockit('ft4_down',1) - - sum2=sum(cd2*conjg(cd2))/(real(NMAX)/real(NDOWN)) + sum2=sum(cd2*conjg(cd2))/(real(NZZ)/real(NDOWN)) if(sum2.gt.0.0) cd2=cd2/sqrt(sum2) ! Sample rate is now 12000/16 = 750 samples/second do isync=1,2 @@ -208,22 +229,21 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & idfmax=12 idfstp=3 ibmin=0 - ibmax=216 !Max DT = 216/750 = 0.288 s + ibmax=800 ibstp=4 else idfmin=idfbest-4 idfmax=idfbest+4 idfstp=1 ibmin=max(0,ibest-5) - ibmax=min(ibest+5,NMAX/NDOWN-1) + ibmax=min(ibest+5,NZZ/NDOWN-1) ibstp=1 endif ibest=-1 smax=-99. idfbest=0 + call timer('sync4d ',0) do idf=idfmin,idfmax,idfstp - - call clockit('sync4d ',0) do istart=ibmin,ibmax,ibstp call sync4d(cd2,istart,ctwk2(:,idf),1,sync) !Find sync power if(sync.gt.smax) then @@ -232,20 +252,20 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & idfbest=idf endif enddo - call clockit('sync4d ',1) - enddo + call timer('sync4d ',1) enddo f0=f0+real(idfbest) if( f0.le.10.0 .or. f0.ge.4990.0 ) cycle - - call clockit('ft4down ',0) - call ft4_downsample(iwave,dobigfft,f0,cb) !Final downsample with corrected f0 - call clockit('ft4down ',1) +! write(*,3002) smax,ibest/750.0,f0 +!3002 format('b',3f8.2) + call timer('ft4down ',0) + call ft4_downsample(iwave,dobigfft,f0,cb) !Final downsample, corrected f0 + call timer('ft4down ',1) sum2=sum(abs(cb)**2)/(real(NSS)*NN) if(sum2.gt.0.0) cb=cb/sqrt(sum2) cd=cb(ibest:ibest+NN*NSS-1) - call clockit('four2a ',0) + call timer('four2a ',0) do k=1,NN i1=(k-1)*NSS csymb=cd(i1:i1+NSS-1) @@ -253,7 +273,7 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & cs(0:3,k)=csymb(1:4) s4(0:3,k)=abs(csymb(1:4)) enddo - call clockit('four2a ',1) + call timer('four2a ',1) ! Sync quality check is1=0 @@ -322,11 +342,9 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & bmetc(201:204)=bmetb(201:204) bmetc(205:206)=bmeta(205:206) - call clockit('normaliz',0) call normalizebmet(bmeta,2*NN) call normalizebmet(bmetb,2*NN) call normalizebmet(bmetc,2*NN) - call clockit('normaliz',1) hbits=0 where(bmeta.ge.0) hbits=1 @@ -432,10 +450,10 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & endif max_iterations=40 message77=0 - call clockit('bpdecode',0) + call timer('bpdec174',0) call bpdecode174_91(llr,apmask,max_iterations,message77, & cw,nharderror,niterations) - call clockit('bpdecode',1) + call timer('bpdec174',1) if(sum(message77).eq.0) cycle if( nharderror.ge.0 ) then message77=mod(message77+rvec,2) ! remove rvec scrambling @@ -455,35 +473,15 @@ subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, & xsnr=-20.0 endif nsnr=nint(max(-20.0,xsnr)) - freq=f0 - tsig=mod(tbuf + ibest/750.0,100.0) - - write(line,1000) hhmmss,nsnr,tsig,nint(freq),message -1000 format(a6,i4,f5.1,i5,' + ',1x,a37) - l1=index(data_dir,char(0))-1 - if(l1.ge.1) data_dir(l1+1:l1+1)="/" - fname=data_dir(1:l1+1)//'all_ft4.txt' - open(24,file=trim(fname),status='unknown',position='append') - write(24,1002) cdatetime0,nsnr,tsig,nint(freq),message, & - nharderror,nsync_qual,ipass,niterations,iaptype,nsync - if(hhmmss.eq.' ') write(*,1002) cdatetime0,nsnr, & - tsig,nint(freq),message,nharderror,nsync_qual,ipass, & - niterations,iaptype -1002 format(a17,i4,f5.1,i5,' Rx ',a37,6i4) - close(24) - linex(ndecodes)=line + xdt=ibest/750.0 - 0.5 + call this%callback(sync,nsnr,xdt,f0,message,iaptype,qual) if(ibest.ge.ibmax-15) msg0=message !Possible dupe candidate exit endif enddo !Sequence estimation enddo !Candidate list - call clockit('ft4_deco',1) - call clockit2(data_dir) - call clockit('ft4_deco',101) - return - entry get_ft4msg(idecode,line) - line=linex(idecode) - return + return + end subroutine decode -end subroutine ft4_decode +end module ft4_decode diff --git a/lib/jt9.f90 b/lib/jt9.f90 index ff548b46e..7b3b0181e 100644 --- a/lib/jt9.f90 +++ b/lib/jt9.f90 @@ -23,7 +23,7 @@ program jt9 integer :: arglen,stat,offset,remain,mode=0,flow=200,fsplit=2700, & fhigh=4000,nrxfreq=1500,ntrperiod=1,ndepth=1,nexp_decode=0 logical :: read_files = .true., tx9 = .false., display_help = .false. - type (option) :: long_options(25) = [ & + type (option) :: long_options(26) = [ & option ('help', .false., 'h', 'Display this help message', ''), & option ('shmem',.true.,'s','Use shared memory for sample data','KEY'), & option ('tr-period', .true., 'p', 'Tx/Rx period, default MINUTES=1', & @@ -48,10 +48,11 @@ program jt9 option ('fft-threads', .true., 'm', & 'Number of threads to process large FFTs, default THREADS=1', & 'THREADS'), & - option ('jt65', .false., '6', 'JT65 mode', ''), & - option ('jt9', .false., '9', 'JT9 mode', ''), & - option ('ft8', .false., '8', 'FT8 mode', ''), & option ('jt4', .false., '4', 'JT4 mode', ''), & + option ('ft4', .false., '5', 'FT4 mode', ''), & + option ('jt65', .false.,'6', 'JT65 mode', ''), & + option ('ft8', .false., '8', 'FT8 mode', ''), & + option ('jt9', .false., '9', 'JT9 mode', ''), & option ('qra64', .false., 'q', 'QRA64 mode', ''), & option ('sub-mode', .true., 'b', 'Sub mode, default SUBMODE=A', 'A'), & option ('depth', .true., 'd', & @@ -76,7 +77,7 @@ program jt9 nsubmode = 0 do - call getopt('hs:e:a:b:r:m:p:d:f:w:t:9864qTL:S:H:c:G:x:g:X:', & + call getopt('hs:e:a:b:r:m:p:d:f:w:t:98654qTL:S:H:c:G:x:g:X:', & long_options,c,optarg,arglen,stat,offset,remain,.true.) if (stat .ne. 0) then exit @@ -113,6 +114,8 @@ program jt9 mode = 164 case ('4') mode = 4 + case ('5') + mode = 5 case ('6') if (mode.lt.65) mode = mode + 65 case ('9') diff --git a/samples/CMakeLists.txt b/samples/CMakeLists.txt index cab1609cb..6be6a6df2 100644 --- a/samples/CMakeLists.txt +++ b/samples/CMakeLists.txt @@ -1,5 +1,5 @@ set (SAMPLE_FILES - FT4/190106_000115.wav + FT4/190106_000112.wav FT8/181201_180245.wav ISCAT/ISCAT-A/VK7MO_110401_235515.wav ISCAT/ISCAT-B/K0AWU_100714_115000.wav diff --git a/samples/FT4/190106_000112.wav b/samples/FT4/190106_000112.wav new file mode 100644 index 000000000..2c6e0a9d4 Binary files /dev/null and b/samples/FT4/190106_000112.wav differ diff --git a/samples/FT4/190106_000115.wav b/samples/FT4/190106_000115.wav deleted file mode 100644 index cf23159f8..000000000 Binary files a/samples/FT4/190106_000115.wav and /dev/null differ diff --git a/widgets/mainwindow.cpp b/widgets/mainwindow.cpp index 3f195a416..8cc5bc330 100644 --- a/widgets/mainwindow.cpp +++ b/widgets/mainwindow.cpp @@ -169,11 +169,6 @@ extern "C" { void chkcall_(char* w, char* basc_call, bool cok, int len1, int len2); - void ft4_decode_(char* cdatetime, float* tbuf, int* nfa, int* nfb, int* nQSOProgress, - int* nContest, int* nfqso, short int id[], int* ndecodes, char* mycall, - char* hiscall, char* cqstr, char* line, char* ddir, int len1, - int len2, int len3, int len4, int len5, int len6); - void get_ft4msg_(int* idecode, char* line, int len); } @@ -748,13 +743,6 @@ MainWindow::MainWindow(QDir const& temp_directory, bool multiple, connect(&m_guiTimer, &QTimer::timeout, this, &MainWindow::guiUpdate); m_guiTimer.start(100); //### Don't change the 100 ms! ### - - FT4_TxTimer.setSingleShot(true); - connect(&FT4_TxTimer, &QTimer::timeout, this, &MainWindow::stopTx); - - FT4_WriteTxTimer.setSingleShot(true); - connect(&FT4_WriteTxTimer, &QTimer::timeout, this, &MainWindow::FT4_writeTx); - ptt0Timer.setSingleShot(true); connect(&ptt0Timer, &QTimer::timeout, this, &MainWindow::stopTx2); @@ -1333,7 +1321,9 @@ void MainWindow::fixStop() m_hsymStop=((int(m_TRperiod/0.288))/8)*8; } else if (m_mode=="FT8") { m_hsymStop=50; - } + } else if (m_mode=="FT4") { + m_hsymStop=18; +} } //-------------------------------------------------------------- dataSink() @@ -1341,8 +1331,7 @@ void MainWindow::dataSink(qint64 frames) { static float s[NSMAX]; char line[80]; - - int k (frames); + int k(frames); QString fname {QDir::toNativeSeparators(m_config.writeable_data_dir ().absoluteFilePath ("refspec.dat"))}; QByteArray bafname = fname.toLatin1(); const char *c_fname = bafname.data(); @@ -1381,8 +1370,9 @@ void MainWindow::dataSink(qint64 frames) if(m_monitoring || m_diskData) { m_wideGraph->dataSink2(s,m_df3,m_ihsym,m_diskData); } - if(m_mode=="FT4") ft4_rx(k); - if(m_mode=="MSK144" or m_mode=="FT4") return; +// if(m_mode=="FT4") ft4_rx(k); +// if(m_mode=="MSK144" or m_mode=="FT4") return; + if(m_mode=="MSK144") return; fixStop(); if (m_mode == "FreqCal" @@ -1462,7 +1452,7 @@ void MainWindow::dataSink(qint64 frames) if(!m_diskData) { //Always save; may delete later - if(m_mode=="FT8") { + if(m_mode=="FT8" or m_mode=="FT4") { int n=now.time().second() % m_TRperiod; if(n<(m_TRperiod/2)) n=n+m_TRperiod; auto const& period_start=now.addSecs(-n); @@ -1472,11 +1462,13 @@ void MainWindow::dataSink(qint64 frames) m_fnameWE=m_config.save_directory ().absoluteFilePath (period_start.toString ("yyMMdd_hhmm")); } m_fileToSave.clear (); + int samples=m_TRperiod*12000; + if(m_mode=="FT4") samples=18*3456; // the following is potential a threading hazard - not a good // idea to pass pointer to be processed in another thread m_saveWAVWatcher.setFuture (QtConcurrent::run (std::bind (&MainWindow::save_wave_file, - this, m_fnameWE, &dec_data.d2[0], m_TRperiod*12000, m_config.my_callsign(), + this, m_fnameWE, &dec_data.d2[0], samples, m_config.my_callsign(), m_config.my_grid(), m_mode, m_nSubMode, m_freqNominal, m_hisCall, m_hisGrid))); if (m_mode=="WSPR") { QString c2name_string {m_fnameWE + ".c2"}; @@ -1914,14 +1906,6 @@ void MainWindow::keyPressEvent (QKeyEvent * e) break; case Qt::Key_F1: if(bAltF1F5) { - if(m_mode=="FT4") { - if(e->modifiers() & Qt::ControlModifier) { - ft4_tx(1); - } else { - ft4_tx(6); - } - return; - } auto_tx_mode(true); on_txb6_clicked(); return; @@ -1931,10 +1915,6 @@ void MainWindow::keyPressEvent (QKeyEvent * e) } case Qt::Key_F2: if(bAltF1F5) { - if(m_mode=="FT4") { - ft4_tx(2); - return; - } auto_tx_mode(true); on_txb2_clicked(); return; @@ -1944,10 +1924,6 @@ void MainWindow::keyPressEvent (QKeyEvent * e) } case Qt::Key_F3: if(bAltF1F5) { - if(m_mode=="FT4") { - ft4_tx(3); - return; - } auto_tx_mode(true); on_txb3_clicked(); return; @@ -1957,10 +1933,6 @@ void MainWindow::keyPressEvent (QKeyEvent * e) } case Qt::Key_F4: if(bAltF1F5) { - if(m_mode=="FT4") { - ft4_tx(4); - return; - } auto_tx_mode(true); on_txb4_clicked(); return; @@ -1971,10 +1943,6 @@ void MainWindow::keyPressEvent (QKeyEvent * e) } case Qt::Key_F5: if(bAltF1F5) { - if(m_mode=="FT4") { - ft4_tx(5); - return; - } auto_tx_mode(true); on_txb5_clicked(); return; @@ -2720,7 +2688,8 @@ void MainWindow::diskDat() //diskDat() float bw=m_config.RxBandwidth(); if(db > 0.0) degrade_snr_(dec_data.d2,&dec_data.params.kin,&db,&bw); for(int n=1; n<=m_hsymStop; n++) { // Do the waterfall spectra - k=(n+1)*kstep; +// k=(n+1)*kstep; //### Why was this (n+1) ??? ### + k=n*kstep; if(k > dec_data.params.kin) break; dec_data.params.npts8=k/8; dataSink(k); @@ -2842,7 +2811,7 @@ void MainWindow::decode() //decode() m_msec0=QDateTime::currentMSecsSinceEpoch(); if(!m_dataAvailable or m_TRperiod==0) return; ui->DecodeButton->setChecked (true); - if(!dec_data.params.nagain && m_diskData && !m_bFastMode && m_mode!="FT8") { + if(!dec_data.params.nagain && m_diskData && !m_bFastMode && m_mode!="FT8" && m_mode!="FT4") { dec_data.params.nutc=dec_data.params.nutc/100; } if(dec_data.params.nagain==0 && dec_data.params.newdat==1 && (!m_diskData)) { @@ -2852,7 +2821,7 @@ void MainWindow::decode() //decode() imin=imin % 60; if(m_TRperiod>=60) imin=imin - (imin % (m_TRperiod/60)); dec_data.params.nutc=100*ihr + imin; - if(m_mode=="ISCAT" or m_mode=="MSK144" or m_bFast9 or m_mode=="FT8") { + if(m_mode=="ISCAT" or m_mode=="MSK144" or m_bFast9 or m_mode=="FT8" or m_mode=="FT4") { QDateTime t=QDateTime::currentDateTimeUtc().addSecs(2-m_TRperiod); ihr=t.toString("hh").toInt(); imin=t.toString("mm").toInt(); @@ -2902,7 +2871,8 @@ void MainWindow::decode() //decode() if(m_modeTx=="JT65") dec_data.params.ntxmode=65; dec_data.params.nmode=9; if(m_mode=="JT65") dec_data.params.nmode=65; - if(m_mode=="JT65") dec_data.params.ljt65apon = ui->actionEnable_AP_JT65->isVisible () && ui->actionEnable_AP_JT65->isChecked (); + if(m_mode=="JT65") dec_data.params.ljt65apon = ui->actionEnable_AP_JT65->isVisible () && + 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=="JT9+JT65") dec_data.params.nmode=9+65; // = 74 @@ -2911,8 +2881,10 @@ void MainWindow::decode() //decode() dec_data.params.ntxmode=4; } if(m_mode=="FT8") dec_data.params.nmode=8; - if(m_mode=="FT8") dec_data.params.lft8apon = ui->actionEnable_AP_FT8->isVisible () && ui->actionEnable_AP_FT8->isChecked (); + if(m_mode=="FT8") dec_data.params.lft8apon = ui->actionEnable_AP_FT8->isVisible () && + ui->actionEnable_AP_FT8->isChecked (); if(m_mode=="FT8") dec_data.params.napwid=50; + if(m_mode=="FT4") dec_data.params.nmode=5; dec_data.params.ntrperiod=m_TRperiod; dec_data.params.nsubmode=m_nSubMode; if(m_mode=="QRA64") dec_data.params.nsubmode=100 + m_nSubMode; @@ -3057,7 +3029,7 @@ void MainWindow::readFromStdout() //readFromStdout // truncate before line ending chars line_read = line_read.left (p - line_read.constData ()); } - if(m_mode!="FT8") { + if(m_mode!="FT8" and m_mode!="FT4") { //Pad 22-char msg to at least 37 chars line_read = line_read.left(43) + " " + line_read.mid(43); } @@ -3077,7 +3049,7 @@ void MainWindow::readFromStdout() //readFromStdout } return; } else { - if(m_mode=="JT4" or m_mode=="JT65" or m_mode=="QRA64" or m_mode=="FT8") { + if(m_mode=="JT4" or m_mode=="JT65" or m_mode=="QRA64" or m_mode=="FT8" or m_mode=="FT4") { int n=line_read.indexOf("f"); if(n<0) n=line_read.indexOf("d"); if(n>0) { @@ -3137,10 +3109,10 @@ void MainWindow::readFromStdout() //readFromStdout //Right (Rx Frequency) window bool bDisplayRight=bAvgMsg; int audioFreq=decodedtext.frequencyOffset(); - if(m_mode=="FT8") { + if(m_mode=="FT8" or m_mode=="FT4") { auto const& parts = decodedtext.string().remove("<").remove(">") .split (' ', QString::SkipEmptyParts); - if (parts.size () > 6) { + if (parts.size() > 6) { auto for_us = parts[5].contains (m_baseCall) || ("DE" == parts[5] && qAbs (ui->RxFreqSpinBox->value () - audioFreq) <= 10); if(m_baseCall==m_config.my_callsign() and m_baseCall!=parts[5]) for_us=false; @@ -3218,7 +3190,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=="QRA64" or m_mode=="JT4" or m_mode=="JT65" or m_mode=="JT9") { + if(m_mode=="FT8" or m_mode=="FT4" or m_mode=="QRA64" or m_mode=="JT4" or m_mode=="JT65" or m_mode=="JT9") { auto_sequence (decodedtext, 25, 50); } @@ -3417,6 +3389,7 @@ void MainWindow::guiUpdate() if(m_TRperiod==0) m_TRperiod=60; txDuration=0.0; + if(m_modeTx=="FT4") txDuration=0.35 + 105*512/12000.0; // FT4 if(m_modeTx=="FT8") txDuration=1.0 + 79*1920/12000.0; // FT8 if(m_modeTx=="JT4") txDuration=1.0 + 207.0*2520/11025.0; // JT4 if(m_modeTx=="JT9") txDuration=1.0 + 85.0*m_nsps/12000.0; // JT9 @@ -3588,7 +3561,8 @@ void MainWindow::guiUpdate() Q_EMIT m_config.transceiver_ptt (true); //Assert the PTT m_tx_when_ready = true; } - if(!m_bTxTime and !m_tune and m_mode!="FT4") m_btxok=false; //Time to stop transmitting +// if(!m_bTxTime and !m_tune and m_mode!="FT4") m_btxok=false; //Time to stop transmitting + if(!m_bTxTime and !m_tune) m_btxok=false; //Time to stop transmitting } if(m_mode.startsWith ("WSPR") and @@ -3677,7 +3651,7 @@ void MainWindow::guiUpdate() 22, 22); // if(m_modeTx=="WSPR-LF") genwspr_fsk8_(message, msgsent, const_cast (itone), // 22, 22); - if(m_modeTx=="MSK144" or m_modeTx=="FT8") { + if(m_modeTx=="MSK144" or m_modeTx=="FT8" or m_modeTx=="FT4") { char MyCall[6]; char MyGrid[6]; strncpy(MyCall, (m_config.my_callsign()+" ").toLatin1(),6); @@ -3722,6 +3696,17 @@ void MainWindow::guiUpdate() } } } + if(m_modeTx=="FT4") { + int ichk=0; + genft4_(message, &ichk, msgsent, const_cast(itone), 37, 37); + int nsym=103; + int nsps=4*512; + float fsample=48000.0; + float f0=ui->TxFreqSpinBox->value() - m_XIT; + int nwave=(nsym+2)*nsps; + gen_ft4wave_(const_cast(itone),&nsym,&nsps,&fsample,&f0,foxcom_.wave,&nwave); + } + if(SpecOp::EU_VHF==m_config.special_op_id()) { if(m_ntx==2) m_xSent=ui->tx2->text().right(13); if(m_ntx==3) m_xSent=ui->tx3->text().right(13); @@ -3739,7 +3724,7 @@ void MainWindow::guiUpdate() } } - if(m_mode!="FT4") m_currentMessage = QString::fromLatin1(msgsent); + m_currentMessage = QString::fromLatin1(msgsent); m_bCallingCQ = CALLING == m_QSOProgress || m_currentMessage.contains (QRegularExpression {"^(CQ|QRZ) "}); if(m_mode=="FT8" or m_mode=="FT4") { @@ -3784,7 +3769,7 @@ void MainWindow::guiUpdate() if((m_config.prompt_to_log() or m_config.autoLog()) && !m_tune) logQSOTimer.start(0); } - bool b=(m_mode=="FT8") and ui->cbAutoSeq->isChecked(); + bool b=(m_mode=="FT8" or m_mode=="FT4") and ui->cbAutoSeq->isChecked(); if(is_73 and (m_config.disable_TX_on_73() or b)) { m_nextCall=""; //### Temporary: disable use of "TU;" messages; if(m_nextCall!="") { @@ -3857,14 +3842,14 @@ void MainWindow::guiUpdate() m_msgSent0 = current_message; } - if(m_mode!="FT4") { +// if(m_mode!="FT4") { if(!m_tune) write_all("Tx",m_currentMessage); if (m_config.TX_messages () && !m_tune && SpecOp::FOX!=m_config.special_op_id()) { ui->decodedTextBrowser2->displayTransmittedText(current_message, m_modeTx, ui->TxFreqSpinBox->value(),m_bFastMode); } - } +// } switch (m_ntx) { @@ -3928,12 +3913,14 @@ void MainWindow::guiUpdate() if(tHound >= 120 and m_ntx==1) auto_tx_mode(false); } - progressBar.setVisible(!(m_mode=="FT4")); +// progressBar.setVisible(!(m_mode=="FT4")); + progressBar.setVisible(true); if(m_auto and m_mode=="Echo" and m_bEchoTxOK) { progressBar.setMaximum(6); progressBar.setValue(int(m_s6)); } - if(m_mode!="Echo" and m_mode!="FT4") { +// if(m_mode!="Echo" and m_mode!="FT4") { + if(m_mode!="Echo") { if(m_monitoring or m_transmitting) { progressBar.setMaximum(m_TRperiod); int isec=int(fmod(tsec,m_TRperiod)); @@ -4217,11 +4204,7 @@ void MainWindow::on_txb1_clicked() m_ntx=1; m_QSOProgress = REPLYING; ui->txrb1->setChecked(true); - if(m_mode=="FT4") { - ft4_tx(1); - } else { - if(m_transmitting) m_restart=true; - } + if(m_transmitting) m_restart=true; } else { on_txb2_clicked (); @@ -4242,11 +4225,7 @@ void MainWindow::on_txb2_clicked() m_ntx=2; m_QSOProgress = REPORT; ui->txrb2->setChecked(true); - if(m_mode=="FT4") { - ft4_tx(2); - } else { - if(m_transmitting) m_restart=true; - } + if(m_transmitting) m_restart=true; } void MainWindow::on_txb3_clicked() @@ -4254,11 +4233,7 @@ void MainWindow::on_txb3_clicked() m_ntx=3; m_QSOProgress = ROGER_REPORT; ui->txrb3->setChecked(true); - if(m_mode=="FT4") { - ft4_tx(3); - } else { - if(m_transmitting) m_restart=true; - } + if(m_transmitting) m_restart=true; } void MainWindow::on_txb4_clicked() @@ -4266,11 +4241,7 @@ void MainWindow::on_txb4_clicked() m_ntx=4; m_QSOProgress = ROGERS; ui->txrb4->setChecked(true); - if(m_mode=="FT4") { - ft4_tx(4); - } else { - if(m_transmitting) m_restart=true; - } + if(m_transmitting) m_restart=true; } void MainWindow::on_txb4_doubleClicked() @@ -4288,11 +4259,7 @@ void MainWindow::on_txb5_clicked() m_ntx=5; m_QSOProgress = SIGNOFF; ui->txrb5->setChecked(true); - if(m_mode=="FT4") { - ft4_tx(5); - } else { - if(m_transmitting) m_restart=true; - } + if(m_transmitting) m_restart=true; } void MainWindow::on_txb5_doubleClicked() @@ -4306,11 +4273,7 @@ void MainWindow::on_txb6_clicked() m_QSOProgress = CALLING; set_dateTimeQSO(-1); ui->txrb6->setChecked(true); - if(m_mode=="FT4") { - ft4_tx(6); - } else { - if(m_transmitting) m_restart=true; - } + if(m_transmitting) m_restart=true; } void MainWindow::doubleClickOnCall2(Qt::KeyboardModifiers modifiers) @@ -4349,7 +4312,7 @@ void MainWindow::doubleClickOnCall(Qt::KeyboardModifiers modifiers) } return; } - DecodedText message {cursor.block().text()}; + DecodedText message {cursor.block().text().trimmed().remove("TU; ")}; m_bDoubleClicked = true; processMessage (message, modifiers); } @@ -4360,7 +4323,6 @@ void MainWindow::processMessage (DecodedText const& message, Qt::KeyboardModifie auto shift = modifiers.testFlag (Qt::ShiftModifier); auto ctrl = modifiers.testFlag (Qt::ControlModifier); // auto alt = modifiers.testFlag (Qt::AltModifier); - // basic mode sanity checks auto const& parts = message.string ().split (' ', QString::SkipEmptyParts); if (parts.size () < 5) return; @@ -4382,21 +4344,6 @@ void MainWindow::processMessage (DecodedText const& message, Qt::KeyboardModifie ui->TxFreqSpinBox->setValue(frequency); //Set Tx freq } } - if(m_mode=="FT4") { - int i0=message.string().indexOf(" + "); - QString t=message.string().trimmed().mid(i0+4,-1); - int n=0; - if(t==ui->tx1->text()) n=1; - if(t==ui->tx2->text()) n=2; - if(t==ui->tx3->text()) n=3; - if(t==ui->tx4->text()) n=4; - if(t==ui->tx5->currentText()) n=5; - if(t==ui->tx6->text()) n=6; - if(n>0) { - if(ctrl) ui->TxFreqSpinBox->setValue(frequency); - ft4_tx(n); - } - } return; } @@ -4587,6 +4534,7 @@ void MainWindow::processMessage (DecodedText const& message, Qt::KeyboardModifie } else { // no grid on end of msg QString r=message_words.at (3); if(m_QSOProgress >= ROGER_REPORT && (r=="RRR" || r.toInt()==73 || "RR73" == r)) { + if(m_mode=="FT4" and r=="RR73") m_dateTimeRcvdRR73=QDateTime::currentDateTimeUtc(); if(ui->tabWidget->currentIndex()==1) { gen_msg = 5; if (ui->rbGenMsg->isChecked ()) m_ntx=7; @@ -4594,7 +4542,6 @@ void MainWindow::processMessage (DecodedText const& message, Qt::KeyboardModifie } else { m_bTUmsg=false; m_nextCall=""; //### Temporary: disable use of "TU;" message - if(SpecOp::RTTY == m_config.special_op_id() and m_nextCall!="") { // We're in RTTY contest and have "nextCall" queued up: send a "TU; ..." message logQSOTimer.start(0); @@ -4847,16 +4794,6 @@ void MainWindow::processMessage (DecodedText const& message, Qt::KeyboardModifie && !m_bDoubleClicked && m_mode!="FT4") { return; } - if(m_mode=="FT4" and ui->cbAutoSeq->isChecked()) { - if((m_ntx==4 or m_ntx==5) and !m_diskData) { - save_FT4(); - logQSOTimer.start(0); // Log the QSO - } - if((m_ntx==3 and ui->cbFirst->isChecked()) or m_ntx==4 or m_bDoubleClicked) { - QThread::msleep(600); //Wait a bit. ### Is this a good idea??? ### - ft4_tx(m_ntx); - } - } if(m_config.quick_call()) auto_tx_mode(true); m_bDoubleClicked=false; } @@ -5039,7 +4976,8 @@ void MainWindow::genStdMsgs(QString rpt, bool unconditional) QDateTime now=QDateTime::currentDateTimeUtc(); int sinceTx3 = m_dateTimeSentTx3.secsTo(now); int sinceRR73 = m_dateTimeRcvdRR73.secsTo(now); - if(m_bDoubleClicked and (qAbs(sinceTx3-12) <= 3) and (sinceRR73 < 5)) { +// qDebug() << "aa" << m_bDoubleClicked << sinceTx3 << sinceRR73; + if(m_bDoubleClicked and (sinceTx3 < 15) and (sinceRR73 < 3)) { t="TU; " + ui->tx3->text(); ui->tx3->setText(t); } @@ -5647,7 +5585,7 @@ void MainWindow::on_actionFT4_triggered() { m_mode="FT4"; m_modeTx="FT4"; - m_TRperiod=2147483647; + m_TRperiod=6; bool bVHF=m_config.enable_VHF_features(); m_bFast9=false; m_bFastMode=false; @@ -5656,7 +5594,7 @@ void MainWindow::on_actionFT4_triggered() m_nsps=6912; m_FFTSize = m_nsps/2; Q_EMIT FFTSize (m_FFTSize); - m_hsymStop=50; + m_hsymStop=18; setup_status_bar (bVHF); m_toneSpacing=12000.0/512.0; ui->actionFT4->setChecked(true); @@ -5674,7 +5612,7 @@ void MainWindow::on_actionFT4_triggered() ui->label_7->setText("Rx Frequency"); ui->label_6->setText("Band Activity"); ui->decodedTextLabel->setText( " UTC dB DT Freq Message"); - displayWidgets(nWidgets("011010000100111000010000100110001")); + displayWidgets(nWidgets("111010000100111000010000100110001")); ui->txrb2->setEnabled(true); ui->txrb4->setEnabled(true); ui->txrb5->setEnabled(true); @@ -6793,18 +6731,17 @@ void MainWindow::setFreq4(int rxFreq, int txFreq) void MainWindow::handle_transceiver_update (Transceiver::TransceiverState const& s) { - // qDebug () << "MainWindow::handle_transceiver_update:" << s; Transceiver::TransceiverState old_state {m_rigState}; //transmitDisplay (s.ptt ()); - if (s.ptt () && !m_rigState.ptt ()) // safe to start audio - // (caveat - DX Lab Suite Commander) - { - if (m_tx_when_ready && g_iptt) // waiting to Tx and still needed - { - ptt1Timer.start(1000 * m_config.txDelay ()); //Start-of-transmission sequencer delay - } - m_tx_when_ready = false; + if (s.ptt () && !m_rigState.ptt ()) { // safe to start audio + // (caveat - DX Lab Suite Commander) + if (m_tx_when_ready && g_iptt) { // waiting to Tx and still needed + int ms_delay=1000*m_config.txDelay(); + if(m_mode=="FT4") ms_delay=20; + ptt1Timer.start(ms_delay); //Start-of-transmission sequencer delay } + m_tx_when_ready = false; + } m_rigState = s; auto old_freqNominal = m_freqNominal; if (!old_freqNominal) @@ -6955,12 +6892,12 @@ void MainWindow::transmit (double snr) } if (m_modeTx == "FT4") { -// toneSpacing=12000.0/512.0; //Generate Tx waveform from itone[] array + m_dateTimeSentTx3=QDateTime::currentDateTimeUtc(); toneSpacing=-2.0; //Transmit a pre-computed, filtered waveform. Q_EMIT sendMessage (NUM_FT4_SYMBOLS, 512.0, ui->TxFreqSpinBox->value() - m_XIT, - toneSpacing, m_soundOutput, m_config.audio_output_channel (), - true, false, snr, 2); + toneSpacing, m_soundOutput, m_config.audio_output_channel(), + true, false, snr, m_TRperiod); } if (m_modeTx == "QRA64") { @@ -8677,7 +8614,7 @@ void MainWindow::write_all(QString txRx, QString message) t.sprintf("%5d",ui->TxFreqSpinBox->value()); if(txRx=="Tx") msg=" 0 0.0" + t + " " + message; auto time = QDateTime::currentDateTimeUtc (); - if(m_mode!="FT4") time = time.addSecs(-(time.time().second() % m_TRperiod)); + time = time.addSecs(-(time.time().second() % m_TRperiod)); t.sprintf("%10.3f ",m_freqNominal/1.e6); if(m_diskData) { line=m_fileDateTime + t + txRx + " " + m_mode.leftJustified(6,' ') + msg; @@ -8700,221 +8637,6 @@ void MainWindow::write_all(QString txRx, QString message) } } -void MainWindow::ft4_rx(int k) -{ - static int nhsec0=-1; - static bool wrapped=false; - short id[60000]; - const int istep=3456; - const int k_enough=55296; //4.608 s - - if(knhsec) nhsec0=-1; - if(nhsec==nhsec0) return; - if(k=NRING) { - j=j-NRING; - wrapped=true; - } - } - if(j>60000) wrapped=false; - if(m_saveAll and ((k-m_kin0)/12000.0 > 15.0) and !m_diskData) save_FT4(); - - if(k>=NRING) { - if(m_saveAll and !m_diskData) save_FT4(); - //Wrap the ring buffer pointer - k=k-NRING; - dec_data.params.kin=k; - } - - QByteArray ba; - if(m_diskData) { - ba=(m_fileDateTime + ".000").toLatin1(); - } else { - auto time = QDateTime::currentDateTimeUtc (); - ba=time.toString("yyMMdd_hhmmss.sss").toLatin1(); - } - char* cdatetime=ba.data(); - - strncpy(dec_data.params.mycall, (m_config.my_callsign()+" ").toLatin1(),12); - char mycall[13]; - strncpy(mycall,m_config.my_callsign().toLatin1(),12); - char hiscall[13]; - strncpy(hiscall,m_hisCall.toLatin1(),12); - - char line[61]; - int nfqso=1500; - int ndecodes=0; - int nfa=m_wideGraph->nStartFreq(); - int nfb=m_wideGraph->Fmax(); - int nQSOProgress = static_cast ( m_QSOProgress ); - int nContest = static_cast (m_config.special_op_id()); - QString dataDir; - dataDir = m_config.writeable_data_dir ().absolutePath (); - char ddir[512]; - strncpy(ddir,dataDir.toLatin1(), sizeof (ddir) - 1); - char cqstr[4]; - strncpy(cqstr," ",4); - if(SpecOp::NA_VHF == m_config.special_op_id()) strncpy(cqstr,"TEST",4); - if(SpecOp::EU_VHF == m_config.special_op_id()) strncpy(cqstr,"TEST",4); - if(SpecOp::FIELD_DAY == m_config.special_op_id()) strncpy(cqstr,"FD",2); - if(SpecOp::RTTY == m_config.special_op_id()) { - if(m_config.RTTY_Exchange()!="SCC") strncpy(cqstr,"RU",2); - if(m_config.RTTY_Exchange()=="SCC") strncpy(cqstr,"SCC",3); - } - ft4_decode_(cdatetime,&tbuf,&nfa,&nfb,&nQSOProgress,&nContest,&nfqso,id,&ndecodes,&mycall[0],&hiscall[0], - &cqstr[0],&line[0],&ddir[0],17,12,12,4,61,512); - line[60]=0; - for (int idecode=1; idecode<=ndecodes; idecode++) { - get_ft4msg_(&idecode,&line[0],61); - line[60]=0; - QString sline{QString::fromLatin1(line)}; - DecodedText decodedtext {sline.replace(QChar::LineFeed,"")}; - ui->decodedTextBrowser->displayDecodedText (decodedtext,m_baseCall,m_mode, - m_config.DXCC(),m_logBook,m_currentBand,m_config.ppfx()); - -//Right (Rx Frequency) window -// int audioFreq=decodedtext.frequencyOffset(); - auto const& parts = decodedtext.string().remove("<").remove(">") - .split (' ', QString::SkipEmptyParts); - if(parts.size() > 6) { - int iFirstCall=5; - if(parts[5]=="TU;") iFirstCall=6; - auto for_us = parts[iFirstCall].contains(m_baseCall); - if(m_baseCall==m_config.my_callsign() and m_baseCall!=parts[iFirstCall]) for_us=false; - if(m_bCallingCQ && !m_bAutoReply && for_us && ui->cbFirst->isChecked()) { - m_bDoubleClicked=true; - m_bAutoReply = true; - ui->cbFirst->setStyleSheet(""); - } - if(for_us) { - ui->decodedTextBrowser2->displayDecodedText(decodedtext,m_baseCall, - m_mode,m_config.DXCC(),m_logBook,m_currentBand,m_config.ppfx()); - if(decodedtext.string().trimmed().contains(m_inQSOwith)) processMessage(decodedtext); - m_QSOText = decodedtext.string().trimmed (); - } - if(for_us and parts[iFirstCall+2]=="RR73") m_dateTimeRcvdRR73=QDateTime::currentDateTimeUtc(); - write_all("Rx",decodedtext.string().trimmed()); - } - } - nhsec0=nhsec; - if(m_diskData and (k > (dec_data.params.kin-istep))) m_startAnother=m_loopall; - if(m_bNoMoreFiles) { - MessageBox::information_message(this, tr("Just one more file to open.")); - m_bNoMoreFiles=false; - } -} - -void MainWindow::ft4_tx(int ntx) -{ - if(g_iptt!=0) return; //Already transmitting? - static char message[38]; - static char msgsent[38]; - QByteArray ba; - m_ntx=ntx; - setTxMsg(m_ntx); - if(m_ntx == 1) ba=ui->tx1->text().toLocal8Bit(); - if(m_ntx == 2) ba=ui->tx2->text().toLocal8Bit(); - if(m_ntx == 3) ba=ui->tx3->text().toLocal8Bit(); - if(m_ntx == 4) ba=ui->tx4->text().toLocal8Bit(); - if(m_ntx == 5) ba=ui->tx5->currentText().toLocal8Bit(); - if(m_ntx == 6) ba=ui->tx6->text().toLocal8Bit(); - QString msg = QString::fromLatin1(ba.data()); - if(m_ntx==2 or m_ntx==3) m_inQSOwith=m_hisCall; - if(msg.trimmed().length()==0) return; //Don't transmit a blank message, or ... - if(m_diskData) return; //... in response to a decode from disk - ba2msg(ba,message); - int ichk=0; - genft4_(message, &ichk, msgsent, const_cast(itone), 37, 37); - msgsent[37]=0; - m_currentMessage = QString::fromLatin1(msgsent).trimmed(); - tx_status_label.setStyleSheet("QLabel{background-color: #ffff33}"); - tx_status_label.setText("TX: " + m_currentMessage); - if(m_ntx==2 or m_ntx==3) { - QStringList t=ui->tx2->text().split(' ', QString::SkipEmptyParts); - int n=t.size(); - m_xSent=t.at(n-2) + " " + t.at(n-1); - } - auto_tx_mode(true); //Enable Tx - icw[0]=0; - g_iptt = 1; - setRig (); - setXIT (ui->TxFreqSpinBox->value ()); - - int nsym=103; - int nsps=4*512; - float fsample=48000.0; - float f0=ui->TxFreqSpinBox->value() - m_XIT; - int nwave=(nsym+2)*nsps; - gen_ft4wave_(const_cast(itone),&nsym,&nsps,&fsample,&f0,foxcom_.wave,&nwave); - if(m_ntx==3) m_dateTimeSentTx3=QDateTime::currentDateTimeUtc(); - Q_EMIT m_config.transceiver_ptt (true); //Assert the PTT - m_tx_when_ready = true; - qint64 ms=QDateTime::currentMSecsSinceEpoch(); - m_modulator->set_ms0(ms); - FT4_TxTimer.start(4600); //Slightly more than FT4 transmission length - - if (g_iptt == 1 && m_iptt0 == 0) { - auto const& current_message = QString::fromLatin1 (msgsent); - FT4_WriteTxTimer.start(100); //Why is a delay necessary to ensure Tx after Rx in all.txt? - if (m_config.TX_messages () && !m_tune && SpecOp::FOX!=m_config.special_op_id()) { - ui->decodedTextBrowser2->displayTransmittedText(current_message, m_modeTx, - ui->TxFreqSpinBox->value(),m_bFastMode); - } - - switch (m_ntx) - { - case 1: m_QSOProgress = REPLYING; break; - case 2: m_QSOProgress = REPORT; break; - case 3: m_QSOProgress = ROGER_REPORT; break; - case 4: m_QSOProgress = ROGERS; break; - case 5: m_QSOProgress = SIGNOFF; break; - case 6: m_QSOProgress = CALLING; break; - default: break; // determined elsewhere - } - m_transmitting = true; - transmitDisplay (true); - statusUpdate (); - } - m_dateTimeQSOOn=QDateTime::currentDateTimeUtc(); - if(!m_btxok && m_btxok0 && g_iptt==1) stopTx(); - if(m_saveAll and !m_diskData) save_FT4(); -} - -void MainWindow::FT4_writeTx() -{ - write_all("Tx",m_currentMessage); -} - -void MainWindow::save_FT4() -{ - double tsec=(dec_data.params.kin - m_kin0)/12000.0; - if(tsec<4.4) return; //Saved data must be at least 4.4 seconds long. - auto time = QDateTime::currentDateTimeUtc (); - QString t=time.toString("yyMMdd_hhmmss"); - m_fnameWE=m_config.save_directory().absoluteFilePath(t); - -// The following is potential a threading hazard - not a good -// idea to pass pointer to be processed in another thread - int nsamples=dec_data.params.kin - m_kin0 + 1; - m_saveWAVWatcher.setFuture (QtConcurrent::run (std::bind (&MainWindow::save_wave_file, - this, m_fnameWE, &dec_data.d2[m_kin0], nsamples, m_config.my_callsign(), - m_config.my_grid(), m_mode, m_nSubMode, m_freqNominal, m_hisCall, - m_hisGrid))); - - m_kin0=dec_data.params.kin; -} - void MainWindow::chkFT4() { if(m_mode!="FT4") return; diff --git a/widgets/mainwindow.h b/widgets/mainwindow.h index 8be317596..6bce17978 100644 --- a/widgets/mainwindow.h +++ b/widgets/mainwindow.h @@ -46,7 +46,7 @@ #define NUM_MSK144_SYMBOLS 144 //s8 + d48 + s8 + d80 #define NUM_QRA64_SYMBOLS 84 //63 data + 21 sync #define NUM_FT8_SYMBOLS 79 -#define NUM_FT4_SYMBOLS 103 +#define NUM_FT4_SYMBOLS 105 #define NUM_CW_SYMBOLS 250 #define TX_SAMPLE_RATE 48000 #define N_WIDGETS 33 @@ -312,8 +312,6 @@ private slots: void on_comboBoxHoundSort_activated (int index); void not_GA_warning_message (); void checkMSK144ContestType(); - void ft4_rx(int k); - void ft4_tx(int ntx); int setTxMsg(int n); bool stdCall(QString const& w); @@ -583,8 +581,6 @@ private: QTimer minuteTimer; QTimer splashTimer; QTimer p1Timer; - QTimer FT4_TxTimer; - QTimer FT4_WriteTxTimer; QString m_path; QString m_baseCall; @@ -764,8 +760,6 @@ private: void foxTxSequencer(); void foxGenWaveform(int i,QString fm); void writeFoxQSO (QString const& msg); - void FT4_writeTx(); - void save_FT4(); }; extern int killbyname(const char* progName);