From a0acb0607d5de9940345efe403026c06e1efb751 Mon Sep 17 00:00:00 2001
From: Joe Taylor <k1jt@arrl.org>
Date: Sat, 8 Jul 2017 14:06:48 +0000
Subject: [PATCH] Re-commit 7806 and 7807, but disable AP decoding.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@7814 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
---
 lib/fsk4hf/ft8b.f90   | 107 +++++++++++++++--------
 lib/fsk4hf/ft8sim.f90 |  10 ++-
 lib/fsk4hf/genft8.f90 | 110 ++++++++++++------------
 lib/ft8_decode.f90    | 191 +++++++++++++++++++++++-------------------
 lib/jt9.f90           |   8 +-
 mainwindow.cpp        |   5 +-
 6 files changed, 250 insertions(+), 181 deletions(-)

diff --git a/lib/fsk4hf/ft8b.f90 b/lib/fsk4hf/ft8b.f90
index 0091d2046..5a455ff5b 100644
--- a/lib/fsk4hf/ft8b.f90
+++ b/lib/fsk4hf/ft8b.f90
@@ -1,4 +1,4 @@
-subroutine ft8b(dd0,newdat,nfqso,ndepth,icand,sync0,f1,xdt,nharderrors,   &
+subroutine ft8b(dd0,newdat,nfqso,ndepth,icand,sync0,f1,xdt,apsym,nharderrors,   &
      dmin,nbadcrc,message,xsnr)
 
   use timer_module, only: timer
@@ -9,14 +9,17 @@ subroutine ft8b(dd0,newdat,nfqso,ndepth,icand,sync0,f1,xdt,nharderrors,   &
   real a(5)
   real s1(0:7,ND),s2(0:7,NN)
   real ps(0:7)
-  real rxdata(3*ND),llr(3*ND)               !Soft symbols
+  real rxdata(3*ND),llr(3*ND),llrap(3*ND)           !Soft symbols
   real dd0(15*12000)
   integer*1 decoded(KK),apmask(3*ND),cw(3*ND)
+  integer*1 msgbits(KK)
+  integer apsym(KK),rr73(11)
   integer itone(NN)
   complex cd0(3200)
   complex ctwk(32)
   complex csymb(32)
   logical newdat
+  data rr73/-1,1,1,1,1,1,1,-1,1,1,-1/
 
   max_iterations=40
   norder=2
@@ -106,34 +109,70 @@ subroutine ft8b(dd0,newdat,nfqso,ndepth,icand,sync0,f1,xdt,nharderrors,   &
   rxdata=rxdata/rxsig
   ss=0.84
   llr=2.0*rxdata/(ss*ss)
-  apmask=0
-  cw=0
-  call timer('bpd174  ',0)
-  call bpdecode174(llr,apmask,max_iterations,decoded,cw,nharderrors)
-  call timer('bpd174  ',1)
-  dmin=0.0
-  if(nharderrors.lt.0) then
-     call timer('osd174  ',0)
-     call osd174(llr,norder,decoded,cw,nharderrors,dmin)
-     call timer('osd174  ',1)
-  endif
-  nbadcrc=1
-  message='                      '
-  xsnr=-99.0
-  if(count(cw.eq.0).eq.174) go to 900           !Reject the all-zero codeword
-  if( nharderrors.ge.0 .and. dmin.le.30.0 .and. nharderrors .lt. 30) then
-    call chkcrc12a(decoded,nbadcrc)
-  else
-    nharderrors=-1
-    go to 900
-  endif
-  if(nbadcrc.eq.0) then
-     call extractmessage174(decoded,message,ncrcflag,recent_calls,nrecent)
-     call genft8(message,msgsent,itone)
+
+!  do iap=0,3
+  do iap=0,0                            !### Temporary ###
+    if(iap.eq.0) then
+      apmask=0
+      apmask(160:162)=1
+      llrap=llr
+      llrap(160:162)=5.0*apsym(73:75)/ss
+    elseif(iap.eq.1) then
+      apmask=0
+      apmask(88:115)=1   ! mycall
+      apmask(160:162)=1  ! 3 extra bits
+      llrap=0.0
+      llrap(88:115)=5.0*apsym(1:28)/ss
+      llrap(160:162)=5.0*apsym(73:75)/ss
+      where(apmask.eq.0) llrap=llr
+    elseif(iap.eq.2) then
+      apmask=0
+      apmask(88:115)=1   ! mycall
+      apmask(116:143)=1  ! hiscall
+      apmask(160:162)=1  ! 3 extra bits
+      llrap=0.0
+      llrap(88:143)=5.0*apsym(1:56)/ss
+      llrap(160:162)=5.0*apsym(73:75)/ss
+      where(apmask.eq.0) llrap=llr
+    elseif(iap.eq.3) then
+      apmask=0
+      apmask(88:115)=1   ! mycall
+      apmask(116:143)=1  ! hiscall
+      apmask(144:154)=1  ! RRR or 73 
+      apmask(160:162)=1  ! 3 extra bits
+      llrap=0.0
+      llrap(88:143)=5.0*apsym(1:56)/ss
+      llrap(144:154)=5.0*rr73/ss
+      llrap(160:162)=5.0*apsym(73:75)/ss
+      where(apmask.eq.0) llrap=llr
+    endif
+    cw=0
+    call timer('bpd174  ',0)
+    call bpdecode174(llrap,apmask,max_iterations,decoded,cw,nharderrors)
+    call timer('bpd174  ',1)
+    dmin=0.0
+    if(nharderrors.lt.0 .and. ndepth.ge.2) then
+      call timer('osd174  ',0)
+      call osd174(llr,norder,decoded,cw,nharderrors,dmin)
+      call timer('osd174  ',1)
+    endif
+    nbadcrc=1
+    message='                      '
+    xsnr=-99.0
+    if(count(cw.eq.0).eq.174) cycle           !Reject the all-zero codeword
+    if( nharderrors.ge.0 .and. dmin.le.30.0 .and. nharderrors .lt. 30) then
+      call chkcrc12a(decoded,nbadcrc)
+    else
+      nharderrors=-1
+      cycle 
+    endif
+    if(nbadcrc.eq.0) then
+      call extractmessage174(decoded,message,ncrcflag,recent_calls,nrecent)
+      call genft8(message,msgsent,msgbits,itone)
 !     call subtractft8(dd0,itone,f1,xdt2)
-     xsig=0.0
-     xnoi=0.0
-     do i=1,79
+      xsig=0.0
+      xnoi=0.0
+      do i=1,79
         xsig=xsig+s2(itone(i),i)**2
         ios=mod(itone(i)+4,7)
         xnoi=xnoi+s2(ios,i)**2
@@ -142,10 +181,10 @@ subroutine ft8b(dd0,newdat,nfqso,ndepth,icand,sync0,f1,xdt,nharderrors,   &
      if( xnoi.gt.0 .and. xnoi.lt.xsig ) xsnr=xsig/xnoi-1.0
      xsnr=10.0*log10(xsnr)-27.0
      if( xsnr .lt. -24.0 ) xsnr=-24.0
-!     write(50,3050) icand,sync0,f1,xdt,nharderrors,dmin,message
-!3050 format(i3,3f10.3,i5,f10.3,2x,a22)
-  endif
-
-900 continue
+!     write(50,3050) icand,sync0,f1,xdt,nharderrors,dmin,message,iap
+!3050 format(i3,3f10.3,i5,f10.3,2x,a22,i3)
+     return
+    endif
+  enddo
   return
 end subroutine ft8b
diff --git a/lib/fsk4hf/ft8sim.f90 b/lib/fsk4hf/ft8sim.f90
index 158e84e30..127c3d08c 100644
--- a/lib/fsk4hf/ft8sim.f90
+++ b/lib/fsk4hf/ft8sim.f90
@@ -11,6 +11,7 @@ program ft8sim
   complex c0(0:NMAX-1)
   complex c(0:NMAX-1)
   integer itone(NN)
+  integer*1 msgbits(KK)
   integer*2 iwave(NMAX)                  !Generated full-length waveform  
 
 ! Get command-line argument(s)
@@ -44,11 +45,16 @@ program ft8sim
   if(snrdb.gt.90.0) sig=1.0
   txt=NN*NSPS/12000.0
 
-  call genft8(msg,msgsent,itone)         !Source-encode, then get itone()
+  call genft8(msg,msgsent,msgbits,itone)         !Source-encode, then get itone()
   write(*,1000) f0,xdt,txt,snrdb,bw,msgsent
 1000 format('f0:',f9.3,'   DT:',f6.2,'   TxT:',f6.1,'   SNR:',f6.1,    &
           '  BW:',f4.1,2x,a22)
-  
+
+write(*,'(28i1,1x,28i1)') msgbits(1:56)
+write(*,'(16i1)') msgbits(57:72)
+write(*,'(3i1)') msgbits(73:75)
+write(*,'(12i1)') msgbits(76:87)
+ 
 !  call sgran()
   c=0.
   do ifile=1,nfiles
diff --git a/lib/fsk4hf/genft8.f90 b/lib/fsk4hf/genft8.f90
index 7b2535aa5..c5306cc8e 100644
--- a/lib/fsk4hf/genft8.f90
+++ b/lib/fsk4hf/genft8.f90
@@ -1,55 +1,55 @@
-subroutine genft8(msg,msgsent,itone)
-
-! Encode an FT8 message, producing array itone().
-  
-  use crc
-  use packjt
-  include 'ft8_params.f90'
-  character*22 msg,msgsent
-  character*87 cbits
-!  logical checksumok
-  integer*4 i4Msg6BitWords(12)                !72-bit message as 6-bit words
-  integer*1 msgbits(KK),codeword(3*ND)
-  integer*1, target:: i1Msg8BitBytes(11)
-  integer itone(NN)
-  integer icos7(0:6)
-  data icos7/2,5,6,0,4,1,3/                   !Costas 7x7 tone pattern
-
-  call packmsg(msg,i4Msg6BitWords,itype)      !Pack into 12 6-bit bytes
-  call unpackmsg(i4Msg6BitWords,msgsent)      !Unpack to get msgsent
-  i3bit=0                                     !### temporary ###
-  write(cbits,1000) i4Msg6BitWords,32*i3bit
-1000 format(12b6.6,b8.8)
-  read(cbits,1001) i1Msg8BitBytes(1:10)
-1001 format(10b8)
-  i1Msg8BitBytes(10)=iand(i1Msg8BitBytes(10),128+64+32)
-  i1Msg8BitBytes(11)=0
-  icrc12=crc12(c_loc(i1Msg8BitBytes),11)
-
-! For reference, here's how to check the CRC
-!  i1Msg8BitBytes(10)=icrc12/256
-!  i1Msg8BitBytes(11)=iand (icrc12,255)
-!  checksumok = crc12_check(c_loc (i1Msg8BitBytes), 11)
-!  if( checksumok ) write(*,*) 'Good checksum'
-
-  write(cbits,1003) i4Msg6BitWords,i3bit,icrc12
-1003 format(12b6.6,b3.3,b12.12)
-  read(cbits,1004) msgbits
-1004 format(87i1)
-  
-  call encode174(msgbits,codeword)      !Encode the test message
-
-! Message structure: S7 D29 S7 D29 S7
-  itone(1:7)=icos7
-  itone(36+1:36+7)=icos7
-  itone(NN-6:NN)=icos7
-  k=7
-  do j=1,ND
-     i=3*j -2
-     k=k+1
-     if(j.eq.30) k=k+7
-     itone(k)=codeword(i)*4 + codeword(i+1)*2 + codeword(i+2)
-  enddo
-
-  return
-end subroutine genft8
+subroutine genft8(msg,msgsent,msgbits,itone)
+
+! Encode an FT8 message, producing array itone().
+  
+  use crc
+  use packjt
+  include 'ft8_params.f90'
+  character*22 msg,msgsent
+  character*87 cbits
+!  logical checksumok
+  integer*4 i4Msg6BitWords(12)                !72-bit message as 6-bit words
+  integer*1 msgbits(KK),codeword(3*ND)
+  integer*1, target:: i1Msg8BitBytes(11)
+  integer itone(NN)
+  integer icos7(0:6)
+  data icos7/2,5,6,0,4,1,3/                   !Costas 7x7 tone pattern
+
+  call packmsg(msg,i4Msg6BitWords,itype)      !Pack into 12 6-bit bytes
+  call unpackmsg(i4Msg6BitWords,msgsent)      !Unpack to get msgsent
+  i3bit=0                                     !### temporary ###
+  write(cbits,1000) i4Msg6BitWords,32*i3bit
+1000 format(12b6.6,b8.8)
+  read(cbits,1001) i1Msg8BitBytes(1:10)
+1001 format(10b8)
+  i1Msg8BitBytes(10)=iand(i1Msg8BitBytes(10),128+64+32)
+  i1Msg8BitBytes(11)=0
+  icrc12=crc12(c_loc(i1Msg8BitBytes),11)
+
+! For reference, here's how to check the CRC
+!  i1Msg8BitBytes(10)=icrc12/256
+!  i1Msg8BitBytes(11)=iand (icrc12,255)
+!  checksumok = crc12_check(c_loc (i1Msg8BitBytes), 11)
+!  if( checksumok ) write(*,*) 'Good checksum'
+
+  write(cbits,1003) i4Msg6BitWords,i3bit,icrc12
+1003 format(12b6.6,b3.3,b12.12)
+  read(cbits,1004) msgbits
+1004 format(87i1)
+
+  call encode174(msgbits,codeword)      !Encode the test message
+
+! Message structure: S7 D29 S7 D29 S7
+  itone(1:7)=icos7
+  itone(36+1:36+7)=icos7
+  itone(NN-6:NN)=icos7
+  k=7
+  do j=1,ND
+     i=3*j -2
+     k=k+1
+     if(j.eq.30) k=k+7
+     itone(k)=codeword(i)*4 + codeword(i+1)*2 + codeword(i+2)
+  enddo
+
+  return
+end subroutine genft8
diff --git a/lib/ft8_decode.f90 b/lib/ft8_decode.f90
index 460302f47..bb751a539 100644
--- a/lib/ft8_decode.f90
+++ b/lib/ft8_decode.f90
@@ -1,84 +1,107 @@
-module ft8_decode
-
-  type :: ft8_decoder
-     procedure(ft8_decode_callback), pointer :: callback
-   contains
-     procedure :: decode
-  end type ft8_decoder
-
-  abstract interface
-     subroutine ft8_decode_callback (this,sync,snr,dt,freq,nbadcrc,decoded)
-       import ft8_decoder
-       implicit none
-       class(ft8_decoder), intent(inout) :: this
-       real, intent(in) :: sync
-       integer, intent(in) :: snr
-       real, intent(in) :: dt
-       real, intent(in) :: freq
-       integer, intent(in) :: nbadcrc
-       character(len=22), intent(in) :: decoded
-     end subroutine ft8_decode_callback
-  end interface
-
-contains
-
-  subroutine decode(this,callback,iwave,nfqso,newdat,nutc,nfa,    &
-       nfb,nagain,ndepth,nsubmode,mycall,hiscall,hisgrid)
-!use wavhdr
-    use timer_module, only: timer
-    include 'fsk4hf/ft8_params.f90'
-!type(hdr) h
-
-    class(ft8_decoder), intent(inout) :: this
-    procedure(ft8_decode_callback) :: callback
-    real s(NH1,NHSYM)
-    real candidate(3,200)
-    real dd(15*12000)
-    logical, intent(in) :: newdat, nagain
-    character*12 mycall, hiscall
-    character*6 hisgrid
-    integer*2 iwave(15*12000)
-    character datetime*13,message*22
-    save s,dd
-
-    this%callback => callback
-    write(datetime,1001) nutc        !### TEMPORARY ###
-1001 format("000000_",i6.6)
-
-    dd=iwave
-
-    call timer('sync8   ',0)
-    call sync8(dd,nfa,nfb,nfqso,s,candidate,ncand)
-    call timer('sync8   ',1)
-
-    syncmin=2.0
-    do icand=1,ncand
-       sync=candidate(3,icand)
-       if(sync.lt.syncmin) cycle
-       f1=candidate(1,icand)
-       xdt=candidate(2,icand)
-       nsnr0=min(99,nint(10.0*log10(sync) - 25.5))    !### empirical ###
-       call timer('ft8b    ',0)
-       call ft8b(dd,newdat,nfqso,ndepth,icand,sync,f1,xdt,nharderrors,   &
-            dmin,nbadcrc,message,xsnr)
-       nsnr=xsnr  
-       xdt=xdt-0.6
-       call timer('ft8b    ',1)
-       if (associated(this%callback)) call this%callback(sync,nsnr,xdt,   &
-            f1,nbadcrc,message)
-!       write(*,'(f7.2,i5,f7.2,f9.1,i5,f7.2,2x,a22)') sync,nsnr,xdt,f1,nharderrors,dmin,message
-!       write(13,1110) datetime,0,nsnr,xdt,f1,nharderrors,dmin,message
-!1110   format(a13,2i4,f6.2,f7.1,i4,' ~ ',f6.2,2x,a22,'  FT8')
-!       write(51,3051) xdt,f1,sync,dmin,nsnr,nharderrors,nbadcrc,message
-!3051   format(4f9.1,3i5,2x,a22)
-!       flush(51)
-    enddo
-!h=default_header(12000,NMAX)
-!open(10,file='subtract.wav',status='unknown',access='stream')
-!iwave=nint(dd)
-!write(10) h,iwave
-!close(10)
-    return
-  end subroutine decode
-
-end module ft8_decode
+module ft8_decode
+
+  type :: ft8_decoder
+     procedure(ft8_decode_callback), pointer :: callback
+   contains
+     procedure :: decode
+  end type ft8_decoder
+
+  abstract interface
+     subroutine ft8_decode_callback (this,sync,snr,dt,freq,nbadcrc,decoded)
+       import ft8_decoder
+       implicit none
+       class(ft8_decoder), intent(inout) :: this
+       real, intent(in) :: sync
+       integer, intent(in) :: snr
+       real, intent(in) :: dt
+       real, intent(in) :: freq
+       integer, intent(in) :: nbadcrc
+       character(len=22), intent(in) :: decoded
+     end subroutine ft8_decode_callback
+  end interface
+
+contains
+
+  subroutine decode(this,callback,iwave,nfqso,newdat,nutc,nfa,    &
+       nfb,nagain,ndepth,nsubmode,mycall12,hiscall12,hisgrid6)
+!use wavhdr
+    use timer_module, only: timer
+    include 'fsk4hf/ft8_params.f90'
+!type(hdr) h
+
+    class(ft8_decoder), intent(inout) :: this
+    procedure(ft8_decode_callback) :: callback
+    real s(NH1,NHSYM)
+    real candidate(3,200)
+    real dd(15*12000)
+    logical, intent(in) :: newdat, nagain
+    character*12 mycall12, hiscall12
+    character*6 hisgrid6
+    integer*2 iwave(15*12000)
+    integer apsym(KK)
+    character datetime*13,message*22
+    save s,dd
+
+    this%callback => callback
+    write(datetime,1001) nutc        !### TEMPORARY ###
+1001 format("000000_",i6.6)
+
+    if(index(hisgrid6," ").eq.0) hisgrid6="EN50"
+    call ft8apset(mycall12,hiscall12,hisgrid6,apsym)
+
+    dd=iwave
+    call timer('sync8   ',0)
+    call sync8(dd,nfa,nfb,nfqso,s,candidate,ncand)
+    call timer('sync8   ',1)
+
+    syncmin=2.0
+    do icand=1,ncand
+       sync=candidate(3,icand)
+       if(sync.lt.syncmin) cycle
+       f1=candidate(1,icand)
+       xdt=candidate(2,icand)
+       nsnr0=min(99,nint(10.0*log10(sync) - 25.5))    !### empirical ###
+       call timer('ft8b    ',0)
+       call ft8b(dd,newdat,nfqso,ndepth,icand,sync,f1,xdt,apsym,nharderrors,  &
+            dmin,nbadcrc,message,xsnr)
+       nsnr=xsnr  
+       xdt=xdt-0.6
+       call timer('ft8b    ',1)
+       if (associated(this%callback)) call this%callback(sync,nsnr,xdt,   &
+            f1,nbadcrc,message)
+!       write(*,'(f7.2,i5,f7.2,f9.1,i5,f7.2,2x,a22)') sync,nsnr,xdt,f1,nharderrors,dmin,message
+!       write(13,1110) datetime,0,nsnr,xdt,f1,nharderrors,dmin,message
+!1110   format(a13,2i4,f6.2,f7.1,i4,' ~ ',f6.2,2x,a22,'  FT8')
+!       write(51,3051) xdt,f1,sync,dmin,nsnr,nharderrors,nbadcrc,message
+!3051   format(4f9.1,3i5,2x,a22)
+!       flush(51)
+    enddo
+!h=default_header(12000,NMAX)
+!open(10,file='subtract.wav',status='unknown',access='stream')
+!iwave=nint(dd)
+!write(10) h,iwave
+!close(10)
+    return
+  end subroutine decode
+
+end module ft8_decode
+
+subroutine ft8apset(mycall12,hiscall12,hisgrid6,apsym)
+  parameter(NAPM=4,KK=87)
+  character*12 mycall12,hiscall12
+  character*22 msg,msgsent
+  character*6 mycall,hiscall
+  character*6 hisgrid6
+  character*4 hisgrid
+  integer apsym(KK)
+  integer*1 msgbits(KK)
+  integer itone(KK)
+  
+  mycall=mycall12(1:6)
+  hiscall=hiscall12(1:6)
+  hisgrid=hisgrid6(1:4) 
+  msg=mycall//' '//hiscall//' '//hisgrid
+  call genft8(msg,msgsent,msgbits,itone)
+  apsym=2*msgbits-1 
+  return
+  end subroutine ft8apset 
diff --git a/lib/jt9.f90 b/lib/jt9.f90
index b223a85c5..394dbdb64 100644
--- a/lib/jt9.f90
+++ b/lib/jt9.f90
@@ -50,7 +50,7 @@ program jt9
         'THREADS'),                                                          &
     option ('jt65', .false., '6', 'JT65 mode', ''),                          &
     option ('jt9', .false., '9', 'JT9 mode', ''),                            &
-    option ('ft9', .false., '8', 'FT8 mode', ''),                            &
+    option ('ft8', .false., '8', 'FT8 mode', ''),                            &
     option ('jt4', .false., '4', 'JT4 mode', ''),                            &
     option ('qra64', .false., 'q', 'QRA64 mode', ''),                        &
     option ('sub-mode', .true., 'b', 'Sub mode, default SUBMODE=A', 'A'),    &
@@ -264,9 +264,9 @@ program jt9
 
      shared_data%params%minsync=0       !### TEST ONLY
 !     shared_data%params%nfqso=1500     !### TEST ONLY
-     mycall="G3WDG       "              !### TEST ONLY
-     hiscall="VK7MO       "             !### TEST ONLY
-     hisgrid="QE37        "             !### TEST ONLY
+!     mycall="G3WDG       "              !### TEST ONLY
+!     hiscall="VK7MO       "             !### TEST ONLY
+!     hisgrid="QE37        "             !### TEST ONLY
      if(mode.eq.164 .and. nsubmode.lt.100) nsubmode=nsubmode+100
 
      shared_data%params%naggressive=0
diff --git a/mainwindow.cpp b/mainwindow.cpp
index 4c786998e..78578e3ca 100644
--- a/mainwindow.cpp
+++ b/mainwindow.cpp
@@ -75,7 +75,7 @@ extern "C" {
               int len1, int len2, int len3, int len4, int len5);
 //  float s[], int* jh, char line[], char mygrid[],
 
-  void genft8_(char* msg, char* msgsent, int itone[], int len1, int len2);
+  void genft8_(char* msg, char* msgsent, char ft8msgbits[], int itone[], int len1, int len2);
 
   void gen4_(char* msg, int* ichk, char* msgsent, int itone[],
                int* itext, int len1, int len2);
@@ -132,6 +132,7 @@ extern "C" {
 }
 
 int volatile itone[NUM_ISCAT_SYMBOLS];	//Audio tones for all Tx symbols
+char volatile ft8msgbits[75]; 	        //packed 75 bit ft8 message
 int volatile icw[NUM_CW_SYMBOLS];	      //Dits for CW ID
 struct dec_data dec_data;               // for sharing with Fortran
 
@@ -3058,7 +3059,7 @@ void MainWindow::guiUpdate()
                                     len1, len1);
         if(m_mode=="WSPR-LF") genwspr_fsk8_(message, msgsent, const_cast<int *> (itone),
                                     len1, len1);
-        if(m_mode=="FT8") genft8_(message, msgsent, const_cast<int *> (itone), len1, len1);
+        if(m_mode=="FT8") genft8_(message, msgsent, const_cast<char *> (ft8msgbits), const_cast<int *> (itone), len1, len1);
         if(m_modeTx=="MSK144") {
           bool bcontest=m_config.contestMode();
           char MyGrid[6];