Old-style "NA VHF Contest" mode removed from all Fortran routines.

This commit is contained in:
Joe Taylor 2018-07-10 15:09:42 -04:00
parent 189c7bae67
commit d95d2df5b6
30 changed files with 64 additions and 86 deletions

View File

@ -443,7 +443,6 @@ set (wsjt_FSRCS
lib/filbig.f90
lib/ft8/filt8.f90
lib/fitcal.f90
lib/fix_contest_msg.f90
lib/flat1.f90
lib/flat1a.f90
lib/flat1b.f90
@ -593,7 +592,6 @@ set (wsjt_FSRCS
lib/sync9w.f90
lib/synciscat.f90
lib/timf2.f90
lib/to_contest_msg.f90
lib/tweak1.f90
lib/twkfreq.f90
lib/ft8/twkfreq1.f90

View File

@ -21,8 +21,8 @@ messages:
- "Always generate new-style (77-bit) messages."
- "Decode only 77-bit messages
4. (K9AN -- MOSTLY DONE) New-style messages can be as long as 37 characters. We'll
need to allow for that in a number of places.
4. (K9AN -- MOSTLY DONE) New-style messages can be as long as 37
characters. We'll need to allow for that in a number of places.
5. (K9AN -- DONE) Subroutine genft8() will need to parse the message to be
transmitted, determine the effective message type i3 and possibly

View File

@ -9,7 +9,7 @@ subroutine encode4(message,ncode)
integer*1 data0(13),symbol(216)
call chkmsg(message,cok,nspecial,flip)
call packmsg(message,dgen,itype,.false.) !Pack 72-bit message into 12 six-bit symbols
call packmsg(message,dgen,itype) !Pack 72-bit message into 12 six-bit symbols
call entail(dgen,data0)
call encode232(data0,206,symbol) !Convolutional encoding
call interleave4(symbol,1) !Apply JT4 interleaving

View File

@ -73,27 +73,27 @@ subroutine extract(s3,nadd,mode65,ntrials,naggressive,ndepth,nflip, &
apsymbols(1,1:4)=(/62,32,32,49/) ! CQ
if(len_trim(mycall).gt.0) then
apmessage=mycall//" "//mycall//" RRR"
call packmsg(apmessage,ap,itype,.false.)
call packmsg(apmessage,ap,itype)
if(itype.ne.1) ap=-1
apsymbols(2,1:4)=ap(1:4)
!write(*,*) 'mycall symbols ',ap(1:4)
if(len_trim(hiscall).gt.0) then
apmessage=mycall//" "//hiscall//" RRR"
call packmsg(apmessage,ap,itype,.false.)
call packmsg(apmessage,ap,itype)
if(itype.ne.1) ap=-1
apsymbols(3,1:9)=ap(1:9)
apsymbols(4,:)=ap
apmessage=mycall//" "//hiscall//" 73"
call packmsg(apmessage,ap,itype,.false.)
call packmsg(apmessage,ap,itype)
if(itype.ne.1) ap=-1
apsymbols(5,:)=ap
if(len_trim(hisgrid(1:4)).gt.0) then
apmessage=mycall//' '//hiscall//' '//hisgrid(1:4)
call packmsg(apmessage,ap,itype,.false.)
call packmsg(apmessage,ap,itype)
if(itype.ne.1) ap=-1
apsymbols(6,:)=ap
apmessage='CQ'//' '//hiscall//' '//hisgrid(1:4)
call packmsg(apmessage,ap,itype,.false.)
call packmsg(apmessage,ap,itype)
if(itype.ne.1) ap=-1
apsymbols(7,:)=ap
endif
@ -211,7 +211,7 @@ subroutine extract(s3,nadd,mode65,ntrials,naggressive,ndepth,nflip, &
correct(1:63)=tmp(1:63)
call interleave63(correct,63,1)
call graycode65(correct,63,1)
call unpackmsg(dat4,decoded,.false.,' ') !Unpack the user message
call unpackmsg(dat4,decoded,' ') !Unpack the user message
ncount=0
if(iand(dat4(10),8).ne.0) ltext=.true.
endif

View File

@ -57,7 +57,7 @@ subroutine extract4(sym0,ncount,decoded)
read(c72,1102) data4
1102 format(12b6)
call unpackmsg(data4,decoded,.false.,' ')
call unpackmsg(data4,decoded,' ')
if(decoded(1:6).eq.'000AAA') then
! decoded='***WRONG MODE?***'
decoded=' '

View File

@ -11,7 +11,7 @@ subroutine extractmessage77(decoded77,msgreceived)
read(cbits,'(12b6)') i4Dec6BitWords
read(cbits,'(72x,i5.5)') i5bit
if( i5bit .eq. 0 ) then
call unpackmsg(i4Dec6BitWords,msgreceived,.false.,' ')
call unpackmsg(i4Dec6BitWords,msgreceived,' ')
endif
return
end subroutine extractmessage77

View File

@ -66,8 +66,8 @@ allocate ( rxdata(N), llr(N) )
! msg="K1JT K9AN EN50"
msg="G4WJS K9AN EN50"
call packmsg(msg,i4Msg6BitWords,itype,.false.) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,.false.,'') !Unpack to get msgsent
call packmsg(msg,i4Msg6BitWords,itype) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,'') !Unpack to get msgsent
write(*,*) "message sent ",msgsent
i4=0

View File

@ -30,7 +30,7 @@ subroutine extractmessage174(decoded,msgreceived,ncrcflag)
enddo
i4Dec6BitWords(ibyte)=itmp
enddo
call unpackmsg(i4Dec6BitWords,msgreceived,.false.,' ')
call unpackmsg(i4Dec6BitWords,msgreceived,' ')
ncrcflag=1
else
msgreceived=' '

View File

@ -30,7 +30,7 @@ subroutine extractmessage174_91(decoded,msgreceived,ncrcflag)
enddo
i4Dec6BitWords(ibyte)=itmp
enddo
call unpackmsg(i4Dec6BitWords,msgreceived,.false.,' ')
call unpackmsg(i4Dec6BitWords,msgreceived,' ')
ncrcflag=1
else
msgreceived=' '

View File

@ -17,7 +17,6 @@ program ft8code
character*6 mygrid6
character bad*1,msgtype*10
character*87 cbits
logical bcontest
integer itone(NN)
integer dgen(12)
integer*1 msgbits(KK),decoded(KK),decoded0(KK)
@ -36,17 +35,10 @@ program ft8code
go to 999
endif
bcontest=.false.
call getarg(1,msg) !Message to be transmitted
if(len(trim(msg)).eq.2 .and. msg(1:2).eq.'-t') then
testmsg(NTEST+1)='KA1ABC RR73; WB9XYZ <KH1/KH7Z> -11'
nmsg=NTEST+1
else if(len(trim(msg)).eq.2 .and. msg(1:2).eq.'-c') then
bcontest=.true.
call getarg(2,mygrid6)
call getarg(3,msg)
msgchk=msg
nmsg=1
else
msgchk=msg
call fmtmsg(msgchk,iz) !To upper case; collapse multiple blanks
@ -63,7 +55,7 @@ program ft8code
! Generate msgsent, msgbits, and itone
if(index(msg,';').le.0) then
call packmsg(msg(1:22),dgen,itype,bcontest)
call packmsg(msg(1:22),dgen,itype)
msgtype=""
if(itype.eq.1) msgtype="Std Msg"
if(itype.eq.2) msgtype="Type 1 pfx"
@ -72,7 +64,7 @@ program ft8code
if(itype.eq.5) msgtype="Type 2 sfx"
if(itype.eq.6) msgtype="Free text"
i3bit=0
call genft8(msg(1:22),mygrid6,bcontest,i3bit,msgsent,msgbits,itone)
call genft8(msg(1:22),mygrid6,i3bit,msgsent,msgbits,itone)
else
call foxgen_wrap(msg,msgbits,itone)
i3bit=1
@ -86,7 +78,6 @@ program ft8code
decoded=decoded0
if(i3bit.eq.0) then
if(bcontest) call fix_contest_msg(mygrid6,message)
bad=" "
comment=' '
if(itype.ne.6 .and. message.ne.msgchk) bad="*"

View File

@ -1,4 +1,4 @@
subroutine genft8(msg37,mygrid,bcontest,i3,n3,isync,msgsent37,msgbits77,itone)
subroutine genft8(msg37,mygrid,i3,n3,isync,msgsent37,msgbits77,itone)
! Encode an FT8 message, producing array itone().
@ -9,7 +9,7 @@ subroutine genft8(msg37,mygrid,bcontest,i3,n3,isync,msgsent37,msgbits77,itone)
character*37 msg37,msgsent37
character*6 mygrid
character*87 cbits
logical bcontest,checksumok
logical checksumok
integer*4 i4Msg6BitWords(12) !72-bit message as 6-bit words
integer*1 msgbits(KK),codeword(3*ND)
integer*1 msgbits77(77)
@ -21,8 +21,8 @@ subroutine genft8(msg37,mygrid,bcontest,i3,n3,isync,msgsent37,msgbits77,itone)
if(isync.eq.2 ) goto 900
msg=msg37(1:22)
call packmsg(msg,i4Msg6BitWords,istdtype,bcontest) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,bcontest,mygrid) !Unpack to get msgsent
call packmsg(msg,i4Msg6BitWords,istdtype) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,mygrid) !Unpack to get msgsent
msgsent37(1:22)=msgsent
msgsent37(23:37)=' '
@ -56,7 +56,7 @@ subroutine genft8(msg37,mygrid,bcontest,i3,n3,isync,msgsent37,msgbits77,itone)
900 continue
call genft8_174_91(msg37,mygrid,bcontest,i3,n3,msgsent37,msgbits77,itone)
call genft8_174_91(msg37,mygrid,i3,n3,msgsent37,msgbits77,itone)
return
end subroutine genft8

View File

@ -1,4 +1,4 @@
subroutine genft8_174_91(msg,mygrid,bcontest,i3,n3,msgsent,msgbits,itone)
subroutine genft8_174_91(msg,mygrid,i3,n3,msgsent,msgbits,itone)
! Encode an FT8 message, producing array itone().
@ -7,7 +7,6 @@ subroutine genft8_174_91(msg,mygrid,bcontest,i3,n3,msgsent,msgbits,itone)
character msg*37,msgsent*37
character*6 mygrid
character*77 c77
logical bcontest
integer*1 msgbits(77),codeword(174)
integer itone(79)
integer icos7(0:6)

View File

@ -67,8 +67,8 @@ allocate ( rxdata(N), llr(N) )
msg="K1JT K9AN EN50"
! msg="G4WJS K9AN EN50"
call packmsg(msg,i4Msg6BitWords,itype,.false.) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,.false.,grid) !Unpack to get msgsent
call packmsg(msg,i4Msg6BitWords,itype) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,grid) !Unpack to get msgsent
write(*,*) "message sent ",msgsent
i4=0

View File

@ -26,8 +26,8 @@ subroutine gen4(msg0,ichk,msgsent,itone,itype)
message=msg0
call fmtmsg(message,iz)
call packmsg(message,i4Msg6BitWords,itype,.false.) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,.false.,' ') !Unpack to get msgsent
call packmsg(message,i4Msg6BitWords,itype) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,' ') !Unpack to get msgsent
if(ichk.ne.0) go to 999
call encode4(message,itone) !Encode the information bits
i1=index(message,'-')

View File

@ -44,8 +44,8 @@ subroutine gen65(msg0,ichk,msgsent,itone,itype)
ntest=0
if(flip.lt.0.0) ntest=1
if(nspecial.eq.0) then
call packmsg(message,dgen,itype,.false.) !Pack message into 72 bits
call unpackmsg(dgen,msgsent,.false.,' ') !Unpack to get message sent
call packmsg(message,dgen,itype) !Pack message into 72 bits
call unpackmsg(dgen,msgsent,' ') !Unpack to get message sent
msgsent(20:22)=cok
call fmtmsg(msgsent,iz)
if(ichk.ne.0) go to 999 !Return if checking only

View File

@ -37,8 +37,8 @@ subroutine gen9(msg0,ichk,msgsent,i4tone,itype)
message=message(i+1:)
enddo
call packmsg(message,i4Msg6BitWords,itype,.false.) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,.false.,' ') !Unpack to get msgsent
call packmsg(message,i4Msg6BitWords,itype) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,' ') !Unpack to get msgsent
if(ichk.ne.0) go to 999
call entail(i4Msg6BitWords,i1Msg8BitBytes) !Add tail, make 8-bit bytes
nsym2=206

View File

@ -1,4 +1,4 @@
subroutine genmsk_128_90(msg0,mygrid,ichk,bcontest,msgsent,i4tone,itype)
subroutine genmsk_128_90(msg0,mygrid,ichk,msgsent,i4tone,itype)
! s8 + 48bits + s8 + 80 bits = 144 bits (72ms message duration)
!
! Encode an MSK144 message
@ -29,7 +29,6 @@ subroutine genmsk_128_90(msg0,mygrid,ichk,bcontest,msgsent,i4tone,itype)
integer*1 msgbits(77)
integer*1 bitseq(144) !Tone #s, data and sync (values 0-1)
integer*1 s8(8)
logical bcontest
real*8 pp(12)
real*8 xi(864),xq(864),pi,twopi
data s8/0,1,1,1,0,0,1,0/

View File

@ -37,8 +37,8 @@ subroutine genqra64(msg0,ichk,msgsent,itone,itype)
enddo
call chkmsg(message,cok,nspecial,flip)
call packmsg(message,dgen,itype,.false.) !Pack message into 72 bits
call unpackmsg(dgen,msgsent,.false.,' ') !Unpack to get message sent
call packmsg(message,dgen,itype) !Pack message into 72 bits
call unpackmsg(dgen,msgsent,' ') !Unpack to get message sent
if(ichk.ne.0) go to 999 !Return if checking only
call qra64_enc(dgen,sent) !Encode using QRA64

View File

@ -88,7 +88,7 @@ subroutine hint65(s3,mrs,mrs2,nadd,nflip,mycall,hiscall,hisgrid,qual,decoded)
if(m.eq.2) msg='CQ '//call2(i)//' '//grid2(i)
endif
call fmtmsg(msg,iz)
call packmsg(msg,dgen,itype,.false.) !Pack message into 72 bits
call packmsg(msg,dgen,itype) !Pack message into 72 bits
call rs_encode(dgen,sym_rev) !RS encode
sym(0:62)=sym_rev(62:0:-1)
sym1(0:62,j)=sym

View File

@ -1,4 +1,4 @@
subroutine hspec(id2,k,nutc0,ntrpdepth,nrxfreq,ntol,bmsk144,bcontest, &
subroutine hspec(id2,k,nutc0,ntrpdepth,nrxfreq,ntol,bmsk144, &
btrain,pcoeffs,ingain,mycall,hiscall,bshmsg,bswl,datadir,green,s, &
jh,pxmax,dbNoGain,line1,mygrid)
@ -23,7 +23,7 @@ subroutine hspec(id2,k,nutc0,ntrpdepth,nrxfreq,ntol,bmsk144,bcontest, &
character*12 mycall,hiscall
character*6 mygrid
integer*2 id2(0:120*12000-1)
logical*1 bmsk144,bcontest,bshmsg,btrain,bswl
logical*1 bmsk144,bshmsg,btrain,bswl
real green(0:JZ-1)
real s(0:63,0:JZ-1)
real x(512)
@ -96,7 +96,7 @@ subroutine hspec(id2,k,nutc0,ntrpdepth,nrxfreq,ntol,bmsk144,bcontest, &
tt2=sum(float(abs(id2(k0:k0+3583))))
if(tt1.ne.0.0 .and. tt2.ne.0) then
call mskrtd(id2(k-7168+1:k),nutc0,tsec,ntol,nrxfreq,ndepth, &
mycall,mygrid,hiscall,bshmsg,bcontest,btrain,pcoeffs,bswl,&
mycall,mygrid,hiscall,bshmsg,btrain,pcoeffs,bswl, &
datadir,line1)
endif
endif

View File

@ -61,7 +61,7 @@ program JT65code
go to 10
endif
call packmsg(msg1,dgen,itype,.false.) !Pack message into 12 six-bit bytes
call packmsg(msg1,dgen,itype) !Pack message into 12 six-bit bytes
msgtype=""
if(itype.eq.1) msgtype="Std Msg"
if(itype.eq.2) msgtype="Type 1 pfx"
@ -77,7 +77,7 @@ program JT65code
call graycode(sent,63,-1,tmp) !Remove Gray code
call interleave63(tmp,-1) !Remove interleaving
call rs_decode(tmp,era,0,recd,nerr) !Decode the message
call unpackmsg(recd,decoded,.false.,' ') !Unpack the user message
call unpackmsg(recd,decoded,' ') !Unpack the user message
if(cok.eq."OOO") decoded(20:22)=cok
call fmtmsg(decoded,iz)

View File

@ -175,7 +175,7 @@ program jt65sim
! write(msg,1010) call1,call2,nint(xsnr)
!1010 format(a5,1x,a5,1x,i3.2)
!###
call packmsg(msg,dgen,itype,.false.) !Pack message into 12 six-bit bytes
call packmsg(msg,dgen,itype) !Pack message into 12 six-bit bytes
call rs_encode(dgen,sent) !Encode using RS(63,12)
call interleave63(sent,1) !Interleave channel symbols
call graycode65(sent,63,1) !Apply Gray code

View File

@ -84,7 +84,7 @@ subroutine jt9fano(i1SoftSymbols,limit,nlim,msg)
enddo
call unpackbits(i4DecodedBytes,nbytes,8,i1DecodedBits)
call packbits(i1DecodedBits,12,6,i4Decoded6BitWords)
call unpackmsg(i4Decoded6BitWords,msg,.false.,' ') !Unpack decoded msg
call unpackmsg(i4Decoded6BitWords,msg,' ') !Unpack decoded msg
if(index(msg,'000AAA ').gt.0) msg=' '
endif

View File

@ -53,8 +53,8 @@ allocate ( codeword(N), decoded(K), message(K) )
allocate ( lratio(N), rxdata(N), rxavgd(N), yy(N), llr(N) )
msg="K9AN K1JT EN50"
call packmsg(msg,i4Msg6BitWords,itype,.false.) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,.false.,' ') !Unpack to get msgsent
call packmsg(msg,i4Msg6BitWords,itype) !Pack into 12 6-bit bytes
call unpackmsg(i4Msg6BitWords,msgsent,' ') !Unpack to get msgsent
write(*,*) "message sent ",msgsent
i4=0

View File

@ -1,5 +1,5 @@
subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
bshmsg,bcontest,btrain,pcoeffs,bswl,datadir,line)
bshmsg,btrain,pcoeffs,bswl,datadir,line)
! Real-time decoder for MSK144.
! Analysis block size = NZ = 7168 samples, t_block = 0.597333 s
@ -39,7 +39,7 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
real xmc(NPATTERNS)
real*8 pcoeffs(5)
logical*1 bshmsg,bcontest,btrain,bswl
logical*1 bshmsg,btrain,bswl
logical*1 first
logical*1 bshdecode
logical*1 seenb4
@ -208,7 +208,6 @@ subroutine mskrtd(id2,nutc0,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall, &
nsnrlast=nsnr
if(.not. bshdecode) then
call update_hasharray(recent_calls,nrecent,nhasharray)
if(bcontest) call fix_contest_msg(mygrid,msgreceived)
endif
write(line,1020) nutc0,nsnr,tdec,nint(fest),decsym,msgreceived, &
navg,ncorrected,eyeopening,char(0)

View File

@ -398,7 +398,7 @@ subroutine packbits(dbits,nsymd,m0,sym)
900 return
end subroutine unpackgrid
subroutine packmsg(msg0,dat,itype,bcontest)
subroutine packmsg(msg0,dat,itype)
! Packs a JT4/JT9/JT65 message into twelve 6-bit symbols
@ -419,14 +419,10 @@ subroutine packbits(dbits,nsymd,m0,sym)
character*12 c1,c2
character*4 c3
character*6 grid6
logical text1,text2,text3,bcontest
logical text1,text2,text3
itype=1
if(bcontest) then
call to_contest_msg(msg0,msg)
else
msg=msg0
end if
msg=msg0
call fmtmsg(msg,iz)
if(msg(1:3).eq.'CQ ' .and. msg(4:4).ge.'0' .and. msg(4:4).le.'9' &
@ -538,13 +534,13 @@ subroutine packbits(dbits,nsymd,m0,sym)
return
end subroutine packmsg
subroutine unpackmsg(dat,msg,bcontest,mygrid)
subroutine unpackmsg(dat,msg,mygrid)
parameter (NBASE=37*36*10*27*27*27)
parameter (NGBASE=180*180)
integer dat(:)
character c1*12,c2*12,grid*4,msg*22,grid6*6,psfx*4,junk2*4,mygrid*6
logical cqnnn,bcontest
logical cqnnn
cqnnn=.false.
nc1=ishft(dat(1),22) + ishft(dat(2),16) + ishft(dat(3),10)+ &
@ -658,8 +654,6 @@ subroutine packbits(dbits,nsymd,m0,sym)
msg(4:4).ge.'A' .and. msg(4:4).le.'Z' .and. &
msg(5:5).eq.' ') msg='CQ '//msg(3:)
if(bcontest) call fix_contest_msg(mygrid,msg)
if(msg(1:5).eq.'CQ 00' .and. msg(6:6).ge.'0' .and. &
msg(6:6).le.'9') msg='CQ '//msg(6:)

View File

@ -128,7 +128,7 @@ subroutine qra64a(dd,npts,nutc,nf1,nf2,nfqso,ntol,mode64,minsync,ndepth, &
10 decoded=' '
if(irc.ge.0) then
call unpackmsg(dat4,decoded,.false.,' ') !Unpack the user message
call unpackmsg(dat4,decoded,' ') !Unpack the user message
call fmtmsg(decoded,iz)
if(index(decoded,"000AAA ").ge.1) then
! Suppress a certain type of garbage decode.

View File

@ -30,11 +30,11 @@ program QRA64code
do imsg=1,nmsg
if(nmsg.gt.1) msg=testmsg(imsg)
call fmtmsg(msg,iz) !To upper, collapse mult blanks
call fmtmsg(msg,iz) !To upper, collapse mult blanks
msg0=msg !Input message
call chkmsg(msg,cok,nspecial,flip) !See if it includes "OOO" report
msg1=msg !Message without "OOO"
call packmsg(msg1,dgen,itype,.false.) !Pack message into 12 six-bit bytes
call packmsg(msg1,dgen,itype) !Pack message into 12 six-bit bytes
msgtype=""
if(itype.eq.1) msgtype="Std Msg"
if(itype.eq.2) msgtype="Type 1 pfx"
@ -45,7 +45,7 @@ program QRA64code
call qra64_enc(dgen,sent) !Encode using QRA64
call unpackmsg(dgen,decoded,.false.,' ') !Unpack the user message
call unpackmsg(dgen,decoded,' ') !Unpack the user message
call fmtmsg(decoded,iz)
ii=imsg
write(*,1020) ii,msg0,decoded,itype,msgtype

View File

@ -1,4 +1,4 @@
function stdmsg(msg0,bcontest,mygrid)
function stdmsg(msg0,mygrid)
! Is msg0 a standard "JT-style" message?
@ -7,14 +7,13 @@ function stdmsg(msg0,bcontest,mygrid)
character*22 msg0,msg1,msg
character*6 mygrid
integer dat(12)
logical(c_bool), value :: bcontest
logical(c_bool) :: stdmsg
msg1=msg0
i0=index(msg1,' OOO ')
if(i0.gt.10) msg1=msg0(1:i0)
call packmsg(msg0,dat,itype,logical(bcontest))
call unpackmsg(dat,msg,logical(bcontest),mygrid)
call packmsg(msg0,dat,itype)
call unpackmsg(dat,msg,mygrid)
stdmsg=(msg.eq.msg1) .and. (itype.ge.0) .and. itype.ne.6
return

View File

@ -70,13 +70,13 @@ extern "C" {
float *m_pxmax);
void hspec_(short int d2[], int* k, int* nutc0, int* ntrperiod, int* nrxfreq, int* ntol,
bool* bmsk144, bool* bcontest, bool* btrain, double const pcoeffs[], int* ingain,
bool* bmsk144, bool* btrain, double const pcoeffs[], int* ingain,
char mycall[], char hiscall[], bool* bshmsg, bool* bswl, char ddir[], float green[],
float s[], int* jh, float *pxmax, float *rmsNoGain, char line[], char mygrid[],
fortran_charlen_t, fortran_charlen_t, fortran_charlen_t, fortran_charlen_t,
fortran_charlen_t);
void genft8_(char* msg, char* MyGrid, bool* bcontest, int* i3, int* n3, int* isync, char* msgsent,
void genft8_(char* msg, char* MyGrid, int* i3, int* n3, int* isync, char* msgsent,
char ft8msgbits[], int itone[], fortran_charlen_t, fortran_charlen_t,
fortran_charlen_t);
@ -88,7 +88,7 @@ extern "C" {
void gen9_(char* msg, int* ichk, char* msgsent, int itone[],
int* itext, fortran_charlen_t, fortran_charlen_t);
void genmsk_128_90_(char* msg, char* MyGrid, int* ichk, bool* bcontest,
void genmsk_128_90_(char* msg, char* MyGrid, int* ichk,
char* msgsent, int itone[], int* itext, fortran_charlen_t,
fortran_charlen_t, fortran_charlen_t);
@ -1506,7 +1506,7 @@ void MainWindow::fastSink(qint64 frames)
float pxmax = 0;
float rmsNoGain = 0;
int ftol = ui->sbFtol->value ();
hspec_(dec_data.d2,&k,&nutc0,&nTRpDepth,&RxFreq,&ftol,&bmsk144,&bcontest,
hspec_(dec_data.d2,&k,&nutc0,&nTRpDepth,&RxFreq,&ftol,&bmsk144,
&m_bTrain,m_phaseEqCoefficients.constData(),&m_inGain,&dec_data.params.mycall[0],
&dec_data.params.hiscall[0],&bshmsg,&bswl,
&ddir[0],fast_green,fast_s,&fast_jh,&pxmax,&rmsNoGain,&line[0],&dec_data.params.mygrid[0],
@ -3468,13 +3468,12 @@ void MainWindow::guiUpdate()
if(m_modeTx=="WSPR-LF") genwspr_fsk8_(message, msgsent, const_cast<int *> (itone),
22, 22);
if(m_modeTx=="MSK144" or m_modeTx=="FT8") {
bool bcontest=ui->cbVHFcontest->isChecked();
char MyCall[6];
char MyGrid[6];
strncpy(MyCall, (m_config.my_callsign()+" ").toLatin1(),6);
strncpy(MyGrid, (m_config.my_grid()+" ").toLatin1(),6);
if(m_modeTx=="MSK144") {
genmsk_128_90_(message, MyGrid, &ichk, &bcontest, msgsent, const_cast<int *> (itone),
genmsk_128_90_(message, MyGrid, &ichk, msgsent, const_cast<int *> (itone),
&m_currentMessageType, 37, 6, 37);
if(m_restart) {
int nsym=144;
@ -3503,7 +3502,7 @@ void MainWindow::guiUpdate()
if(!m_config.bGenerate77() and itype == 6 and (m_i3>0 or m_n3>0)) m_isync=2;
if(m_config.bGenerate77()) m_isync=2;
char ft8msgbits[77];
genft8_(message, MyGrid, &bcontest, &m_i3, &m_n3, &m_isync, msgsent,
genft8_(message, MyGrid, &m_i3, &m_n3, &m_isync, msgsent,
const_cast<char *> (ft8msgbits), const_cast<int *> (itone), 37, 6, 37);
if(m_config.bFox()) {