diff --git a/CMakeLists.txt b/CMakeLists.txt
index cd770c66a..b07964a7c 100644
--- a/CMakeLists.txt
+++ b/CMakeLists.txt
@@ -71,7 +71,7 @@ message (STATUS "******************************************************")
 
 include (set_build_type)
 # RC 0 or omitted is a development build, GA is a General Availability release build
-set_build_type (RC 4)
+set_build_type (RC 5)
 set (wsjtx_VERSION "${PROJECT_VERSION_MAJOR}.${PROJECT_VERSION_MINOR}.${PROJECT_VERSION_PATCH}${BUILD_TYPE_REVISION}")
 
 #
diff --git a/Configuration.cpp b/Configuration.cpp
index 2047ca023..cc977fd7c 100644
--- a/Configuration.cpp
+++ b/Configuration.cpp
@@ -1436,7 +1436,9 @@ void Configuration::impl::initialize_models ()
   ui_->TX_audio_source_button_group->button (rig_params_.audio_source)->setChecked (true);
   ui_->CAT_poll_interval_spin_box->setValue (rig_params_.poll_interval);
   ui_->opCallEntry->setText (opCall_);
+  ui_->udp_server_line_edit->setEnabled(false);
   ui_->udp_server_line_edit->setText (udp_server_name_);
+  ui_->udp_server_line_edit->setEnabled(true);
   on_udp_server_line_edit_editingFinished ();
   ui_->udp_server_port_spin_box->setValue (udp_server_port_);
   load_network_interfaces (ui_->udp_interfaces_combo_box, udp_interface_names_);
@@ -2538,6 +2540,28 @@ void Configuration::impl::on_udp_server_line_edit_textChanged (QString const&)
 
 void Configuration::impl::on_udp_server_line_edit_editingFinished ()
 {
+  if (this->isVisible())
+  {
+    int q1,q2,q3,q4;
+    char tmpbuf[2];
+    int n = sscanf(ui_->udp_server_line_edit->text ().trimmed ().toLatin1(), "%d.%d.%d.%d.%1s", &q1, &q2, &q3, &q4, tmpbuf);
+    const char *iperr;
+    switch(n)
+    {
+      case 0: iperr = "Error before first number";break;
+      case 1: iperr = "Error between first and second number";break;
+      case 2: iperr = "Error between second and third number";break;
+      case 3: iperr = "Error between third and fourth number";break;
+      case 4: iperr = ""; break;
+      case 5: iperr = "Invalid characters after IP address"; break;
+      default: iperr = "Unknown error parsing network address";
+    }
+    if (n != 4)
+    {
+       MessageBox::warning_message (this, tr ("Error in network address"), tr (iperr));
+       return;
+    }
+
   if (udp_server_name_edited_)
     {
       auto const& server = ui_->udp_server_line_edit->text ().trimmed ();
@@ -2557,6 +2581,7 @@ void Configuration::impl::on_udp_server_line_edit_editingFinished ()
           check_multicast (ha);
         }
     }
+  }
 }
 
 void Configuration::impl::host_info_results (QHostInfo host_info)
diff --git a/Network/MessageClient.cpp b/Network/MessageClient.cpp
index 94f564bc5..1991f1593 100644
--- a/Network/MessageClient.cpp
+++ b/Network/MessageClient.cpp
@@ -137,6 +137,7 @@ void MessageClient::impl::host_info_results (QHostInfo host_info)
   if (QHostInfo::NoError != host_info.error ())
     {
       Q_EMIT self_->error ("UDP server DNS lookup failed: " + host_info.errorString ());
+      return;
     }
   else
     {
diff --git a/Transceiver/DXLabSuiteCommanderTransceiver.cpp b/Transceiver/DXLabSuiteCommanderTransceiver.cpp
index 2014c1044..02f8ad636 100644
--- a/Transceiver/DXLabSuiteCommanderTransceiver.cpp
+++ b/Transceiver/DXLabSuiteCommanderTransceiver.cpp
@@ -437,15 +437,14 @@ QString DXLabSuiteCommanderTransceiver::command_with_reply (QString const& cmd)
           };
     }
 
-  auto result = commander_->readAll ();
-  // qDebug () << "result: " << result;
-  // for (int i = 0; i < result.size (); ++i)
-  //   {
-  //     qDebug () << i << ":" << hex << int (result[i]);
-  //   }
+  QString result = commander_->readAll ();
 
+  if (result != NULL)
+  {
   CAT_TRACE (cmd << " -> " << QString {result});
   return result;                // converting raw UTF-8 bytes to QString
+  }
+  return "";
 }
 
 bool DXLabSuiteCommanderTransceiver::write_to_port (QString const& s)
diff --git a/Transceiver/PollingTransceiver.cpp b/Transceiver/PollingTransceiver.cpp
index 5ddbd66a7..95845283d 100644
--- a/Transceiver/PollingTransceiver.cpp
+++ b/Transceiver/PollingTransceiver.cpp
@@ -117,6 +117,10 @@ void PollingTransceiver::do_post_ptt (bool p)
       retries_ = polls_to_stabilize;
       //retries_ = 0;             // fast feedback on PTT
     }
+  else
+    {
+      next_state_.ptt(p);         // ensure this is initialized
+    }
 }
 
 bool PollingTransceiver::do_pre_update ()
diff --git a/doc/CMakeLists.txt b/doc/CMakeLists.txt
index 7c48c5449..eb058291b 100644
--- a/doc/CMakeLists.txt
+++ b/doc/CMakeLists.txt
@@ -72,7 +72,7 @@ set (UG_IMGS
   images/config-menu.png
   images/decode-menu.png
   images/download_samples.png
-  images/echo_144.png
+  images/Echo_1296.png
   images/EME_Deep_0.png
   images/EME_Deep_1.png
   images/EME_Deep_2.png
diff --git a/doc/user_guide/en/images/Echo_1296.png b/doc/user_guide/en/images/Echo_1296.png
new file mode 100644
index 000000000..e33af55a0
Binary files /dev/null and b/doc/user_guide/en/images/Echo_1296.png differ
diff --git a/doc/user_guide/en/images/echo_144.png b/doc/user_guide/en/images/echo_144.png
deleted file mode 100644
index 77f80e97a..000000000
Binary files a/doc/user_guide/en/images/echo_144.png and /dev/null differ
diff --git a/doc/user_guide/en/introduction.adoc b/doc/user_guide/en/introduction.adoc
index 2cc1f6917..cead851f7 100644
--- a/doc/user_guide/en/introduction.adoc
+++ b/doc/user_guide/en/introduction.adoc
@@ -70,7 +70,8 @@ provides a mapping facility, archival storage, and many other
 features.
 
 *Echo* mode allows you to detect and measure your own station's echoes
-from the moon, even if they are far below the audible threshold.
+from the moon and to make other measurements useful for optimizing
+your EME station's performance.
 
 _WSJT-X_ provides spectral displays for receiver passbands as wide as
 5 kHz, flexible rig control for nearly all modern radios used by
diff --git a/doc/user_guide/en/new_features.adoc b/doc/user_guide/en/new_features.adoc
index f2bf6b237..5bc46628e 100644
--- a/doc/user_guide/en/new_features.adoc
+++ b/doc/user_guide/en/new_features.adoc
@@ -15,10 +15,11 @@ that station.
 of situations with available _a priori_ (AP) information.
 
 - *Echo* mode now offers a *Clear Avg* button and produces reliable
-measurements of SNR even when Doppler spread is large.  The *Measure*
-function can be used to measure SNR for a received unmodulated carrier
--- for example, a key-down test signal emitted by another station and
-reflected from the Moon.
+measurements of SNR even when Doppler spread is large.  Its *Monitor*
+function can be used to measure SNR for a received unmodulated
+carrier such as a key-down test signal emitted by another station and
+reflected from the Moon, and to measure Sun, Moon, and ground noise as
+aids for optimizing an EME station's performance.
 
 - New buttons on the main window allow quick changes between modes
 FT4, FT8, MSK144, Q65, and JT65.  Another new button allows toggling
diff --git a/doc/user_guide/en/vhf-features.adoc b/doc/user_guide/en/vhf-features.adoc
index e108cdfe4..54fcf2af2 100644
--- a/doc/user_guide/en/vhf-features.adoc
+++ b/doc/user_guide/en/vhf-features.adoc
@@ -280,37 +280,43 @@ being readable by anyone listening in.
 
 === Echo Mode
 
-*Echo* mode allows you to make sensitive measurements of your own
-lunar echoes even when they are too weak to be heard. Select *Echo*
-from the *Mode* menu, aim your antenna at the moon, pick a clear
-frequency, and toggle click *Tx Enable*. _WSJT-X_ will then cycle
-through the following loop every 6 seconds:
+*Echo* mode provides tools for two types of measurements: echoes of
+your transmitted signal from the Moon, and broadband noise power
+received from the Sun, Moon, and possibly other sources including
+nearby ground.  In each case the system noise temperature (noise power
+referred to the antenna terminals, expressed in Kelvin degrees) serves
+as the reference noise level.  Such measurements are widely used for
+optimizing a station's capabilities for Earth-Moon-Earth (EME)
+communication.
 
-1. Transmit a 1500 Hz fixed tone for 2.3 s
-2. Wait about 0.2 s for start of the return echo
-3. Record the received signal for 2.3 s
-4. Analyze, average, and display the results
-5. Repeat from step 1
+For lunar echoes, _WSJT_ generates short fixed-frequency transmissions
+that alternate with reception intervals at the appropriate
+Doppler-shifted frequency.  With *Split Operation* set to *Rig* or
+*Fake It* on the *Settings | Radio* tab, check *Doppler tracking* and
+*Own Echo* on the Astronomical Data window.  Point your antenna at the
+Moon and click *Enable Tx* on the main window to start a sequence of
+echo measurements.  Each cycle takes 6 seconds.  If strong enough,
+echoes will be visible in the waterfall.  Their average spectrum will
+be displayed in the Echo Graph window, and numerical parameters of the
+measurements appear in the main window:
 
-To make a sequence of echo tests:
+image::Echo_1296.png[align="center",alt="Echo 144 MHz"]
 
-- Select *Echo* from the *Mode* menu.
+At the end of each echo cycle a line of data in the main text window
+displays the following information:
 
-- Check *Doppler tracking* and *Constant frequency on the Moon* on the
-Astronomical Data window.
+ UTC       Time in hhmmss format
+ Hour      UTC in hours and decimal fraction
+ Level     Relative received noise power (dB)
+ Doppler   EME Doppler shift at center of lunar disk
+ Width     EME Doppler spread over full lunar disk
+ N         Number of accumulated echo or monitor cycles
+ Q         Estimated quality of averaged data on a 0 – 10 scale
+ DF        Offset of spectral peak from 1500 Hz
+ SNR       Average signal-to-noise ratio (dB/2500 Hz)
+ dBerr     Estimated uncertainty of SNR
 
-- Be sure that your rig control has been set up for _Split Operation_,
-using either *Rig* or *Fake It* on the *Settings | Radio* tab.
-
-- Click *Enable Tx* on the main window to start a sequence of 6-second
-cycles.
-
-- _WSJT-X_ calculates and compensates for Doppler shift automatically.
-As shown in the screen shot below, when proper Doppler corrections
-have been applied your return echo should always appear at the center
-of the plot area on the Echo Graph window.
-
-image::echo_144.png[align="center",alt="Echo 144 MHz"]
+... more to come ...
 
 === Tips for EME
 
diff --git a/lib/avecho.f90 b/lib/avecho.f90
index 645a96db4..90e828d56 100644
--- a/lib/avecho.f90
+++ b/lib/avecho.f90
@@ -1,5 +1,5 @@
-subroutine avecho(id2,ndop,nfrit,nauto,nqual,f1,xlevel,snrdb,db_err,  &
-     dfreq,width,bDiskData)
+subroutine avecho(id2,ndop,nfrit,nauto,navg,nqual,f1,xlevel,snrdb,   &
+     db_err,dfreq,width,bDiskData)
 
   integer TXLENGTH
   parameter (TXLENGTH=27648)           !27*1024
@@ -8,6 +8,8 @@ subroutine avecho(id2,ndop,nfrit,nauto,nqual,f1,xlevel,snrdb,db_err,  &
   integer*2 id2(34560)                 !Buffer for Rx data
   real sa(NZ)      !Avg spectrum relative to initial Doppler echo freq
   real sb(NZ)      !Avg spectrum with Dither and changing Doppler removed
+  real, dimension (:,:), allocatable :: sax
+  real, dimension (:,:), allocatable :: sbx
   integer nsum       !Number of integrations
   real dop0          !Doppler shift for initial integration (Hz)
   real dop           !Doppler shift for current integration (Hz)
@@ -20,8 +22,18 @@ subroutine avecho(id2,ndop,nfrit,nauto,nqual,f1,xlevel,snrdb,db_err,  &
   equivalence (x,c),(ipk,ipkv)
   common/echocom/nclearave,nsum,blue(NZ),red(NZ)
   common/echocom2/fspread_self,fspread_dx
-  save dop0,sa,sb
+  data navg0/-1/
+  save dop0,navg0,sax,sbx
 
+  if(navg.ne.navg0) then
+     if(allocated(sax)) deallocate(sax)
+     if(allocated(sbx)) deallocate(sbx)
+     allocate(sax(1:navg,1:NZ))
+     allocate(sbx(1:navg,1:NZ))
+     nsum=0
+     navg0=navg
+  endif
+  
   fspread=fspread_dx                !### Use the predicted Doppler spread ###
   if(bDiskData) fspread=width
   if(nauto.eq.1) fspread=fspread_self
@@ -44,8 +56,8 @@ subroutine avecho(id2,ndop,nfrit,nauto,nqual,f1,xlevel,snrdb,db_err,  &
   if(nclearave.ne.0) nsum=0
   if(nsum.eq.0) then
      dop0=dop                             !Remember the initial Doppler
-     sa=0.                                !Clear the average arrays
-     sb=0.
+     sax=0.                               !Clear the average arrays
+     sbx=0.
   endif
 
   x(TXLENGTH+1:)=0.
@@ -67,10 +79,14 @@ subroutine avecho(id2,ndop,nfrit,nauto,nqual,f1,xlevel,snrdb,db_err,  &
   endif
 
   nsum=nsum+1
+  j=mod(nsum-1,navg)+1
   do i=1,NZ
-     sa(i)=sa(i) + s(ia+i-2048)    !Center at initial doppler freq
-     sb(i)=sb(i) + s(ib+i-2048)    !Center at expected echo freq
+     sax(j,i)=s(ia+i-2048)    !Center at initial doppler freq
+     sbx(j,i)=s(ib+i-2048)    !Center at expected echo freq
+     sa(i)=sum(sax(1:navg,i))
+     sb(i)=sum(sbx(1:navg,i))
   enddo
+  
   call echo_snr(sa,sb,fspread,blue,red,snrdb,db_err,dfreq,snr_detect)
   nqual=snr_detect-2
   if(nqual.lt.0) nqual=0
@@ -87,12 +103,17 @@ subroutine avecho(id2,ndop,nfrit,nauto,nqual,f1,xlevel,snrdb,db_err,  &
      call smo121(blue,NZ)
   enddo
 
-  ia=200.0/df
-  ib=400.0/df
-  call pctile(red(ia:ib),ib-ia+1,50,bred)
-  red=red-bred
-  call pctile(blue(ia:ib),ib-ia+1,50,bblue)
-  blue=blue-bblue
+  ia=50.0/df
+  ib=250.0/df
+  call pctile(red(ia:ib),ib-ia+1,50,bred1)
+  call pctile(blue(ia:ib),ib-ia+1,50,bblue1)
+  ia=1250.0/df
+  ib=1450.0/df
+  call pctile(red(ia:ib),ib-ia+1,50,bred2)
+  call pctile(blue(ia:ib),ib-ia+1,50,bblue2)
+
+  red=red-0.5*(bred1+bred2)
+  blue=blue-0.5*(bblue1+bblue2)
 
 900 call sleep_msec(10)   !Avoid the "blue Decode button" syndrome
   return
diff --git a/lib/echosim.f90 b/lib/echosim.f90
index 1125bbdb1..96854aaee 100644
--- a/lib/echosim.f90
+++ b/lib/echosim.f90
@@ -8,7 +8,7 @@ program echosim
   character arg*12,fname*17
   complex c0(0:NMAX-1)
   complex c(0:NMAX-1)
-!  complex cwave(0:NWAVE-1)
+  real*4 level_1,level_2
   real*8 f0,dt,twopi,phi,dphi
   real wave(NZ)
   integer*2 iwave(NZ)                  !Generated full-length waveform
@@ -20,9 +20,11 @@ program echosim
 
 ! Get command-line argument(s)
   nargs=iargc()
-  if(nargs.ne.5) then
-     print*,'Usage:    echosim   f0   fdop fspread nfiles snr'
-     print*,'Examples: echosim  1500   0.0   4.0     10   -22'
+  if(nargs.ne.3 .and. nargs.ne.5) then
+     print*,'Usage 1:  echosim   f0   fdop fspread nfiles snr'
+     print*,'Example:  echosim  1500   0.0   4.0     10   -22'
+     print*,'Usage 2:  echosim level_1 level_2 nfiles'
+     print*,'Example:  echosim   30.0    40.0   100'
      go to 999
   endif
 
@@ -32,12 +34,21 @@ program echosim
   read(arg,*) fdop                       !Doppler shift (Hz)
   call getarg(3,arg)
   read(arg,*) fspread             !Frequency spread (Hz) (JHT Lorentzian model)
+
+  if(nargs.eq.3) then
+     level_1=f0
+     level_2=fdop
+     nfiles=fspread
+     snrdb=0.
+     go to 10
+  endif
+  
   call getarg(4,arg)
   read(arg,*) nfiles                     !Number of files
   call getarg(5,arg)
   read(arg,*) snrdb                      !SNR_2500
 
-  twopi=8.d0*atan(1.d0)
+10 twopi=8.d0*atan(1.d0)
   fs=12000.0                             !Sample rate (Hz)
   dt=1.d0/fs                              !Sample interval (s)
   bandwidth_ratio=2500.0/(fs/2.0)
@@ -49,18 +60,23 @@ program echosim
 1000 format('   N   f0     fDop fSpread   SNR  File name'/51('-'))
 
   do ifile=1,nfiles
-     phi=0.d0
-     do i=0,NWAVE-1
-        phi=phi + dphi
-        if(phi.gt.twopi) phi=phi-twopi
-        xphi=phi
-        c0(i)=cmplx(cos(xphi),sin(xphi))
-     enddo
-     c0(NWAVE:)=0.
-     if(fspread.gt.0.0) call fspread_lorentz(c0,fspread)
-     c=sig*c0
-     wave(1:NWAVE)=imag(c(1:NWAVE))
-     peak=maxval(abs(wave))
+     wave=0.
+
+     if(nargs.eq.5) then
+        phi=0.d0
+        do i=0,NWAVE-1
+           phi=phi + dphi
+           if(phi.gt.twopi) phi=phi-twopi
+           xphi=phi
+           c0(i)=cmplx(cos(xphi),sin(xphi))
+        enddo
+        c0(NWAVE:)=0.
+        if(fspread.gt.0.0) call fspread_lorentz(c0,fspread)
+        c=sig*c0
+        wave(1:NWAVE)=imag(c(1:NWAVE))
+        peak=maxval(abs(wave))
+     endif
+
      if(snrdb.lt.90) then
         do i=1,NWAVE                   !Add gaussian noise at specified SNR
            xnoise=gran()
@@ -73,6 +89,10 @@ program echosim
      endif
 
      gain=100.0
+     if(nargs.eq.3) then
+        gain=10.0**(0.05*level_1)
+        if(mod((ifile-1)/10,2).eq.1) gain=10.0**(0.05*level_2)
+     endif
      if(snrdb.lt.90.0) then
        wave=gain*wave
      else
diff --git a/lib/fst4_decode.f90 b/lib/fst4_decode.f90
index 38e8a15bb..5d9ccc827 100644
--- a/lib/fst4_decode.f90
+++ b/lib/fst4_decode.f90
@@ -586,13 +586,26 @@ contains
                         xsig=xsig+s4(itone(i),i)
                      enddo
                      base=candidates(icand,5)
-                     arg=600.0*(xsig/base)-1.0
+                     select case(ntrperiod)
+                        case(15) 
+                           snr_calfac=800.0
+                        case(30) 
+                           snr_calfac=600.0
+                        case(60) 
+                           snr_calfac=430.0
+                        case(120) 
+                           snr_calfac=390.0
+                        case(300) 
+                           snr_calfac=340.0
+                        case(900) 
+                           snr_calfac=320.0
+                        case(1800) 
+                           snr_calfac=320.0
+                        case default
+                     end select
+                     arg=snr_calfac*xsig/base - 1.0
                      if(arg.gt.0.0) then
-                        xsnr=10*log10(arg)-35.5-12.5*log10(nsps/8200.0)
-                        if(ntrperiod.eq.  15) xsnr=xsnr+2
-                        if(ntrperiod.eq.  30) xsnr=xsnr+1
-                        if(ntrperiod.eq. 900) xsnr=xsnr+1
-                        if(ntrperiod.eq.1800) xsnr=xsnr+2
+                        xsnr=10*log10(arg)+10*log10(1.46/2500)+10*log10(8200.0/nsps)
                      else
                         xsnr=-99.9
                      endif
diff --git a/lib/ft8/ft8b.f90 b/lib/ft8/ft8b.f90
index d96cbd9c7..30cd95c83 100644
--- a/lib/ft8/ft8b.f90
+++ b/lib/ft8/ft8b.f90
@@ -287,6 +287,7 @@ subroutine ft8b(dd0,newdat,nQSOProgress,nfqso,nftx,ndepth,nzhsym,lapon,     &
 !          5 : WW_DIGI 
 !          6 : FOX
 !          7 : HOUND
+!          8 : ARRL_DIGI
 !
 ! Conditions that cause us to bail out of AP decoding
         if(ncontest.le.5 .and. iaptype.ge.3 .and. (abs(f1-nfqso).gt.napwid .and. abs(f1-nftx).gt.napwid) ) cycle
@@ -306,6 +307,7 @@ subroutine ft8b(dd0,newdat,nQSOProgress,nfqso,nftx,ndepth,nzhsym,lapon,     &
            if(ncontest.eq.4) llrz(1:29)=apmag*mcqru(1:29)
            if(ncontest.eq.5) llrz(1:29)=apmag*mcqww(1:29)
            if(ncontest.eq.7) llrz(1:29)=apmag*mcq(1:29)
+           if(ncontest.eq.8) llrz(1:29)=apmag*mcqtest(1:29)
            apmask(75:77)=1 
            llrz(75:76)=apmag*(-1)
            llrz(77)=apmag*(+1)
@@ -313,7 +315,7 @@ subroutine ft8b(dd0,newdat,nQSOProgress,nfqso,nftx,ndepth,nzhsym,lapon,     &
 
         if(iaptype.eq.2) then ! MyCall,???,??? 
            apmask=0
-           if(ncontest.eq.0.or.ncontest.eq.1.or.ncontest.eq.5) then
+           if(ncontest.eq.0.or.ncontest.eq.1.or.ncontest.eq.5.or.ncontest.eq.8) then
               apmask(1:29)=1  
               llrz(1:29)=apmag*apsym(1:29)
               apmask(75:77)=1 
@@ -353,7 +355,7 @@ subroutine ft8b(dd0,newdat,nQSOProgress,nfqso,nftx,ndepth,nzhsym,lapon,     &
 
         if(iaptype.eq.3) then ! MyCall,DxCall,??? 
            apmask=0
-           if(ncontest.eq.0.or.ncontest.eq.1.or.ncontest.eq.2.or.ncontest.eq.5.or.ncontest.eq.7) then
+           if(ncontest.eq.0.or.ncontest.eq.1.or.ncontest.eq.2.or.ncontest.eq.5.or.ncontest.eq.7.or.ncontest.eq.8) then
               apmask(1:58)=1  
               llrz(1:58)=apmag*apsym
               apmask(75:77)=1 
@@ -379,7 +381,7 @@ subroutine ft8b(dd0,newdat,nQSOProgress,nfqso,nftx,ndepth,nzhsym,lapon,     &
         if(iaptype.eq.5.and.ncontest.eq.7) cycle !Hound
         if(iaptype.eq.4 .or. iaptype.eq.5 .or. iaptype.eq.6) then  
            apmask=0
-           if(ncontest.le.5 .or. (ncontest.eq.7.and.iaptype.eq.6)) then
+           if(ncontest.le.5 .or. (ncontest.eq.7.and.iaptype.eq.6) .or. ncontest.eq.8) then
               apmask(1:77)=1   ! mycall, hiscall, RRR|73|RR73
               llrz(1:58)=apmag*apsym
               if(iaptype.eq.4) llrz(59:77)=apmag*mrrr 
diff --git a/lib/ft8/sync8.f90 b/lib/ft8/sync8.f90
index 5ea2254ad..f93afe75a 100644
--- a/lib/ft8/sync8.f90
+++ b/lib/ft8/sync8.f90
@@ -1,9 +1,10 @@
-subroutine sync8(dd,nfa,nfb,syncmin,nfqso,maxcand,s,candidate,   &
+subroutine sync8(dd,nfa,nfb,syncmin,nfqso,maxcand,nzhsym,candidate,   &
      ncand,sbase)
 
   include 'ft8_params.f90'
-  parameter (MAXPRECAND=500)
-! Search over +/- 2.5s relative to 0.5s TX start time. 
+  parameter (MAXPRECAND=1000)
+! Maximum sync correlation lag +/- 2.5s relative to 0.5s TX start time. 
+! 2.5s / 0.16s/symbol * 4 samples/symbol = 62.5 lag steps in 2.5s
   parameter (JZ=62)                        
   complex cx(0:NH1)
   real s(NH1,NHSYM)
@@ -12,11 +13,14 @@ subroutine sync8(dd,nfa,nfb,syncmin,nfqso,maxcand,s,candidate,   &
   real x(NFFT1)
   real sync2d(NH1,-JZ:JZ)
   real red(NH1)
+  real red2(NH1)
   real candidate0(3,MAXPRECAND)
   real candidate(3,maxcand)
   real dd(NMAX)
   integer jpeak(NH1)
+  integer jpeak2(NH1)
   integer indx(NH1)
+  integer indx2(NH1)
   integer ii(1)
   integer icos7(0:6)
   data icos7/3,1,4,0,6,5,2/                   !Costas 7x7 tone pattern
@@ -82,11 +86,16 @@ subroutine sync8(dd,nfa,nfb,syncmin,nfqso,maxcand,s,candidate,   &
   enddo
 
   red=0.
+  red2=0.
+  mlag=10
+  mlag2=JZ
   do i=ia,ib
-     ii=maxloc(sync2d(i,-JZ:JZ)) - 1 - JZ
-     j0=ii(1)
-     jpeak(i)=j0
-     red(i)=sync2d(i,j0)
+     ii=maxloc(sync2d(i,-mlag:mlag)) - 1 - mlag 
+     jpeak(i)=ii(1)
+     red(i)=sync2d(i,jpeak(i))
+     ii=maxloc(sync2d(i,-mlag2:mlag2)) - 1 - mlag2
+     jpeak2(i)=ii(1)
+     red2(i)=sync2d(i,jpeak2(i))
   enddo
   iz=ib-ia+1
   call indexx(red(ia:ib),iz,indx)
@@ -100,14 +109,29 @@ subroutine sync8(dd,nfa,nfb,syncmin,nfqso,maxcand,s,candidate,   &
   if(ibase.gt.nh1) ibase=nh1
   base=red(ibase)
   red=red/base
-
+  call indexx(red2(ia:ib),iz,indx2)
+  ibase2=indx2(npctile) - 1 + ia
+  if(ibase2.lt.1) ibase2=1
+  if(ibase2.gt.nh1) ibase2=nh1
+  base2=red2(ibase2)
+  red2=red2/base2
   do i=1,min(MAXPRECAND,iz)
      n=ia + indx(iz+1-i) - 1
-     if(red(n).lt.syncmin.or.isnan(red(n)).or.k.eq.MAXPRECAND) exit
-     k=k+1
-     candidate0(1,k)=n*df
-     candidate0(2,k)=(jpeak(n)-0.5)*tstep
-     candidate0(3,k)=red(n)
+     if(k.ge.MAXPRECAND) exit
+     if( (red(n).ge.syncmin) .and. (.not.isnan(red(n))) ) then 
+        k=k+1
+        candidate0(1,k)=n*df
+        candidate0(2,k)=(jpeak(n)-0.5)*tstep
+        candidate0(3,k)=red(n)
+     endif
+     if(abs(jpeak2(n)-jpeak(n)).eq.0) cycle 
+     if(k.ge.MAXPRECAND) exit
+     if( (red2(n).ge.syncmin) .and. (.not.isnan(red2(n))) ) then
+        k=k+1
+        candidate0(1,k)=n*df
+        candidate0(2,k)=(jpeak2(n)-0.5)*tstep
+        candidate0(3,k)=red2(n)
+     endif
   enddo
   ncand=k
 
@@ -116,7 +140,8 @@ subroutine sync8(dd,nfa,nfb,syncmin,nfqso,maxcand,s,candidate,   &
      if(i.ge.2) then
         do j=1,i-1
            fdiff=abs(candidate0(1,i))-abs(candidate0(1,j))
-           if(abs(fdiff).lt.4.0) then
+           tdiff=abs(candidate0(2,i)-candidate0(2,j))
+           if(abs(fdiff).lt.4.0.and.tdiff.lt.0.04) then
               if(candidate0(3,i).ge.candidate0(3,j)) candidate0(3,j)=0.
               if(candidate0(3,i).lt.candidate0(3,j)) candidate0(3,i)=0.
            endif
@@ -148,6 +173,5 @@ subroutine sync8(dd,nfa,nfb,syncmin,nfqso,maxcand,s,candidate,   &
      endif
   enddo
   ncand=k-1
-
   return
 end subroutine sync8
diff --git a/lib/ft8_decode.f90 b/lib/ft8_decode.f90
index b33629738..4bd637e95 100644
--- a/lib/ft8_decode.f90
+++ b/lib/ft8_decode.f90
@@ -44,7 +44,7 @@ contains
 
     class(ft8_decoder), intent(inout) :: this
     procedure(ft8_decode_callback) :: callback
-    parameter (MAXCAND=300,MAX_EARLY=100)
+    parameter (MAXCAND=600,MAX_EARLY=100)
     real*8 tsec,tseq
     real s(NH1,NHSYM)
     real sbase(NH1)
@@ -80,7 +80,9 @@ contains
        dt0=0.
        f0=0.
     endif
-    if(nutc.ne.nutc0) then
+!Added 41==nzhsym to force a reset if the same wav file is processed twice or more in a row,
+!in which case nutc.eq.nutc0 and ndec(jseq,1) doesn't get reset
+    if(nzhsym==41 .or. (nutc.ne.nutc0)) then
 ! New UTC.  Move previously saved 'a7' data from k=1 to k=0
        iz=ndec(jseq,1)
        dt0(1:iz,jseq,0)  = dt0(1:iz,jseq,1)
@@ -107,6 +109,7 @@ contains
        dd=iwave
        dd1=dd
     endif
+
     if(nzhsym.eq.41) then
        ndecodes=0
        allmessages='                                     '
@@ -114,10 +117,12 @@ contains
     else
        ndecodes=ndec_early
     endif
+
     if(nzhsym.eq.47 .and. ndec_early.eq.0) then
        dd1=dd
        go to 800
     endif
+
     if(nzhsym.eq.47 .and. ndec_early.ge.1) then
        lsubtracted=.false.
        lrefinedt=.true.
@@ -140,6 +145,7 @@ contains
        dd1=dd
        go to 900
     endif
+
     if(nzhsym.eq.50 .and. ndec_early.ge.1 .and. .not.nagain) then
        n=47*3456
        dd(1:n)=dd1(1:n)
@@ -151,6 +157,7 @@ contains
        enddo
        call timer('sub_ft8c',1)
     endif
+
     ifa=nfa
     ifb=nfb
     if(nzhsym.eq.50 .and. nagain) then
@@ -164,11 +171,12 @@ contains
 ! ndepth=2: subtraction, 3 passes, bp+osd (no subtract refinement) 
 ! ndepth=3: subtraction, 3 passes, bp+osd
     npass=3
-    if(ndepth.eq.1) npass=1
+    if(ndepth.eq.1) npass=2
     do ipass=1,npass
       newdat=.true.
       syncmin=1.3
       if(ndepth.le.2) syncmin=1.6
+      if(nzhsym.eq.41) syncmin=2.0
       if(ipass.eq.1) then
         lsubtract=.true.
         ndeep=ndepth
@@ -185,7 +193,7 @@ contains
       endif 
       call timer('sync8   ',0)
       maxc=MAXCAND
-      call sync8(dd,ifa,ifb,syncmin,nfqso,maxc,s,candidate,   &
+      call sync8(dd,ifa,ifb,syncmin,nfqso,maxc,nzhsym,candidate,   &
            ncand,sbase)
       call timer('sync8   ',1)
       do icand=1,ncand
@@ -221,10 +229,6 @@ contains
               if(emedelay.ne.0) xdt=xdt+2.0
               call this%callback(sync,nsnr,xdt,f1,msg37,iaptype,qual)
               call ft8_a7_save(nutc,xdt,f1,msg37)  !Enter decode in table
-!              ii=ndec(jseq,1)
-!              write(41,3041) jseq,ii,nint(f0(ii,jseq,0)),msg0(ii,jseq,0)(1:22),&
-!                   nint(f0(ii,jseq,1)),msg0(ii,jseq,1)(1:22)
-!3041          format(3i5,2x,a22,i5,2x,a22)
            endif
         endif
         call timestamp(tsec,tseq,ctime)
@@ -237,7 +241,7 @@ contains
    if(nzhsym.lt.50) ndec_early=ndecodes
    
 900 continue
-   if(nzhsym.eq.50 .and. ndec(jseq,0).ge.1) then
+   if(lft8apon .and. ncontest.ne.6 .and. ncontest.ne.7 .and. nzhsym.eq.50 .and. ndec(jseq,0).ge.1) then
       newdat=.true.
       do i=1,ndec(jseq,0)
          if(f0(i,jseq,0).eq.-99.0) exit
diff --git a/lib/symspec.f90 b/lib/symspec.f90
index 38189a3c2..49adf105b 100644
--- a/lib/symspec.f90
+++ b/lib/symspec.f90
@@ -55,6 +55,7 @@ subroutine symspec(shared_data,k,TRperiod,nsps,ingain,bLowSidelobes,    &
   endif
 
   if(k.lt.k0) then                             !Start a new data block
+     k0=0
      ja=0
      ssum=0.
      ihsym=0
@@ -64,11 +65,8 @@ subroutine symspec(shared_data,k,TRperiod,nsps,ingain,bLowSidelobes,    &
   sq=0.
   pxmax=0.;
 
-!  dwell_time=0.0001
-!  if(k.gt.k0 .and. npct.gt.0) call blanker(shared_data%id2(k0+1:k),  &
-!       k-k0,dwell_time,npct)
-
   do i=k0+1,k
+     if(k0.eq.0 .and. i.le.10) cycle
      x1=shared_data%id2(i)
      if (abs(x1).gt.pxmax) pxmax = abs(x1);
      sq=sq + x1*x1
diff --git a/lib/testfast9.f90 b/lib/testfast9.f90
index 391d88e5d..0315241f0 100644
--- a/lib/testfast9.f90
+++ b/lib/testfast9.f90
@@ -1,6 +1,6 @@
 program testfast9
 
-  parameter (NMAX=359424)
+  parameter (NMAX=30*12000)
   integer*2 id2(NMAX)
   integer narg(0:11)
   character*80 line(100)
@@ -8,8 +8,8 @@ program testfast9
   
   nargs=iargc()
   if(nargs.ne.2) then
-     print*,'Usage:    testfast9 submode infile'
-     print*,'Example: testfast9 E /data/VE1SKY/K1JT/JT9E/150806_123300.wav'
+     print*,'Usage:   testfast9 submode infile'
+     print*,'Example: testfast9 E 150806_123300.wav'
      go to 999
   endif
   call getarg(1,submode)
diff --git a/map65/astro.cpp b/map65/astro.cpp
index a91c048b4..427518382 100644
--- a/map65/astro.cpp
+++ b/map65/astro.cpp
@@ -7,6 +7,7 @@
 #include <stdio.h>
 #include "SettingsGroup.hpp"
 #include "commons.h"
+#include <math.h>
 
 extern "C" {
   void astrosub_ (int* nyear, int* month, int* nday, double* uth, int* nfreq,
@@ -44,7 +45,7 @@ Astro::~Astro()
 }
 
 void Astro::astroUpdate(QDateTime t, QString mygrid, QString hisgrid,
-                        int fQSO, int nsetftx, int ntxFreq, QString azelDir)
+                        int fQSO, int nsetftx, int ntxFreq, QString azelDir, double xavg)
 {
   static int ntxFreq0=-99;
   char cc[300];
@@ -86,6 +87,65 @@ void Astro::astroUpdate(QDateTime t, QString mygrid, QString hisgrid,
           ntsky,xnr,dgrd);
   ui->astroTextBrowser->setText(" "+ date + "\nUTC: " + utc + "\n" + cc);
 
+  double azOffset=0.0;
+  double elOffset=0.0;
+  double rad=57.2957795131;
+  int iCycle=2;
+// Are we doing pointing tests?
+  bool bPointing=ui->cbPointingTests->isChecked();
+  ui->gbPointing->setVisible(bPointing);
+  if(bPointing) {
+    int nDwell=int(ui->sbDwell->value());
+    if(ui->cbAutoCycle->isChecked()) {
+      iCycle=(t.currentSecsSinceEpoch()%(6*nDwell))/nDwell + 1;
+      if(iCycle==1) {
+        azOffset = -ui->sbOffset->value()/cos(elsun/rad);
+        ui->rb1->setChecked(true);
+      }
+      if(iCycle==2 or iCycle==5) {
+        ui->rb2->setChecked(true);
+      }
+      if(iCycle==3) {
+        azOffset = +ui->sbOffset->value()/cos(elsun/rad);
+        ui->rb3->setChecked(true);
+      }
+      if(iCycle==4) {
+        elOffset = -ui->sbOffset->value();
+        ui->rb4->setChecked(true);
+      }
+      if(iCycle==6) {
+        elOffset = +ui->sbOffset->value();
+        ui->rb6->setChecked(true);
+      }
+    }
+    if(ui->cbOnOff->isChecked()) {
+      iCycle=(t.currentSecsSinceEpoch()%(2*nDwell))/nDwell + 1;
+      if(iCycle==1) {
+        azOffset = -ui->sbOffset->value()/cos(elsun/rad);
+        ui->rb1->setChecked(true);
+      }
+      if(iCycle==2) {
+        ui->rb2->setChecked(true);
+      }
+    }
+    if(ui->cbAutoCycle->isChecked() or ui->cbOnOff->isChecked()) {
+      QFile f("pointing.out");
+      if(f.open(QIODevice::WriteOnly | QIODevice::Append)) {
+        QTextStream out(&f);
+        out << t.toString("yyyy-MMM-dd hh:mm:ss");
+        sprintf(cc,"%7.1f %7.1f   %d %7.1f %7.1f %10.1f %7.2f\n",
+                azsun,elsun,iCycle,azOffset,elOffset,xavg,10.0*log10(xavg));
+        out << cc;
+        f.close();
+      }
+    }
+  } else {
+    ui->rb2->setChecked(true);
+    ui->cbAutoCycle->setChecked(false);
+    ui->cbOnOff->setChecked(false);
+  }
+
+// Write pointing data to azel.dat
   QString fname=azelDir+"/azel.dat";
   QFile f(fname);
   if(!f.open(QIODevice::WriteOnly | QIODevice::Text)) {
@@ -107,7 +167,7 @@ void Astro::astroUpdate(QDateTime t, QString mygrid, QString hisgrid,
           "%3d,%1d,fQSO\n"
           "%3d,%1d,fQSO2\n",
           nhr,nmin,isec,azmoon,elmoon,
-          nhr,nmin,isec,azsun,elsun,
+          nhr,nmin,isec,azsun+azOffset,elsun+elOffset,
           nhr,nmin,isec,0.0,0.0,
           nfreq,ndop,ndop00,
           fQSO,nsetftx,
@@ -120,3 +180,14 @@ void Astro::setFontSize(int n)
 {
   ui->astroTextBrowser->setFontPointSize(n);
 }
+
+void Astro::on_cbAutoCycle_clicked(bool checked)
+{
+  if(checked) ui->cbOnOff->setChecked(false);
+}
+
+void Astro::on_cbOnOff_clicked(bool checked)
+{
+  if(checked) ui->cbAutoCycle->setChecked(false);
+}
+
diff --git a/map65/astro.h b/map65/astro.h
index f425f3e73..6b574237f 100644
--- a/map65/astro.h
+++ b/map65/astro.h
@@ -15,10 +15,14 @@ class Astro : public QWidget
 public:
   explicit Astro (QString const& settings_filename, QWidget *parent = 0);
   void astroUpdate(QDateTime t, QString mygrid, QString hisgrid,
-                   int fQSO, int nsetftx, int ntxFreq, QString azelDir);
+                   int fQSO, int nsetftx, int ntxFreq, QString azelDir, double xavg);
   void setFontSize(int n);
   ~Astro ();
 
+private slots:
+  void on_cbOnOff_clicked(bool checked);
+  void on_cbAutoCycle_clicked(bool checked);
+
 private:
   Ui::Astro *ui;
   QString m_settings_filename;
diff --git a/map65/astro.ui b/map65/astro.ui
index 30cce70bb..991a002f4 100644
--- a/map65/astro.ui
+++ b/map65/astro.ui
@@ -6,30 +6,242 @@
    <rect>
     <x>0</x>
     <y>0</y>
-    <width>262</width>
+    <width>441</width>
     <height>483</height>
    </rect>
   </property>
   <property name="windowTitle">
    <string>Form</string>
   </property>
-  <widget class="QTextBrowser" name="astroTextBrowser">
+  <widget class="QGroupBox" name="gbPointing">
+   <property name="geometry">
+    <rect>
+     <x>269</x>
+     <y>19</y>
+     <width>151</width>
+     <height>431</height>
+    </rect>
+   </property>
+   <property name="title">
+    <string/>
+   </property>
+   <widget class="QRadioButton" name="rb1">
+    <property name="geometry">
+     <rect>
+      <x>10</x>
+      <y>100</y>
+      <width>30</width>
+      <height>17</height>
+     </rect>
+    </property>
+    <property name="text">
+     <string>1</string>
+    </property>
+   </widget>
+   <widget class="QRadioButton" name="rb2">
+    <property name="geometry">
+     <rect>
+      <x>60</x>
+      <y>100</y>
+      <width>40</width>
+      <height>17</height>
+     </rect>
+    </property>
+    <property name="text">
+     <string>2, 5</string>
+    </property>
+    <property name="checked">
+     <bool>true</bool>
+    </property>
+   </widget>
+   <widget class="QRadioButton" name="rb3">
+    <property name="geometry">
+     <rect>
+      <x>110</x>
+      <y>100</y>
+      <width>30</width>
+      <height>17</height>
+     </rect>
+    </property>
+    <property name="text">
+     <string>3</string>
+    </property>
+   </widget>
+   <widget class="QRadioButton" name="rb4">
+    <property name="geometry">
+     <rect>
+      <x>60</x>
+      <y>150</y>
+      <width>30</width>
+      <height>17</height>
+     </rect>
+    </property>
+    <property name="text">
+     <string>4</string>
+    </property>
+   </widget>
+   <widget class="QRadioButton" name="rb6">
+    <property name="geometry">
+     <rect>
+      <x>60</x>
+      <y>50</y>
+      <width>30</width>
+      <height>17</height>
+     </rect>
+    </property>
+    <property name="text">
+     <string>6</string>
+    </property>
+   </widget>
+   <widget class="QDoubleSpinBox" name="sbOffset">
+    <property name="geometry">
+     <rect>
+      <x>10</x>
+      <y>230</y>
+      <width>130</width>
+      <height>22</height>
+     </rect>
+    </property>
+    <property name="alignment">
+     <set>Qt::AlignCenter</set>
+    </property>
+    <property name="prefix">
+     <string>Offset   </string>
+    </property>
+    <property name="suffix">
+     <string>  deg</string>
+    </property>
+    <property name="decimals">
+     <number>1</number>
+    </property>
+    <property name="minimum">
+     <double>0.500000000000000</double>
+    </property>
+    <property name="maximum">
+     <double>20.000000000000000</double>
+    </property>
+    <property name="singleStep">
+     <double>0.500000000000000</double>
+    </property>
+    <property name="value">
+     <double>2.500000000000000</double>
+    </property>
+   </widget>
+   <widget class="QCheckBox" name="cbAutoCycle">
+    <property name="geometry">
+     <rect>
+      <x>30</x>
+      <y>330</y>
+      <width>91</width>
+      <height>17</height>
+     </rect>
+    </property>
+    <property name="text">
+     <string>Auto Cycle</string>
+    </property>
+   </widget>
+   <widget class="QCheckBox" name="cbOnOff">
+    <property name="geometry">
+     <rect>
+      <x>30</x>
+      <y>380</y>
+      <width>70</width>
+      <height>17</height>
+     </rect>
+    </property>
+    <property name="text">
+     <string>On Off</string>
+    </property>
+   </widget>
+   <widget class="QSpinBox" name="sbDwell">
+    <property name="geometry">
+     <rect>
+      <x>10</x>
+      <y>280</y>
+      <width>130</width>
+      <height>22</height>
+     </rect>
+    </property>
+    <property name="alignment">
+     <set>Qt::AlignCenter</set>
+    </property>
+    <property name="suffix">
+     <string>   s</string>
+    </property>
+    <property name="prefix">
+     <string>Dwell   </string>
+    </property>
+    <property name="minimum">
+     <number>10</number>
+    </property>
+    <property name="maximum">
+     <number>300</number>
+    </property>
+    <property name="singleStep">
+     <number>10</number>
+    </property>
+   </widget>
+  </widget>
+  <widget class="QWidget" name="">
    <property name="geometry">
     <rect>
      <x>0</x>
      <y>10</y>
-     <width>256</width>
-     <height>451</height>
+     <width>258</width>
+     <height>471</height>
     </rect>
    </property>
-   <property name="font">
-    <font>
-     <family>Courier New</family>
-     <pointsize>20</pointsize>
-     <weight>75</weight>
-     <bold>true</bold>
-    </font>
-   </property>
+   <layout class="QVBoxLayout" name="verticalLayout">
+    <item>
+     <widget class="QTextBrowser" name="astroTextBrowser">
+      <property name="font">
+       <font>
+        <family>Courier New</family>
+        <pointsize>20</pointsize>
+        <weight>75</weight>
+        <bold>true</bold>
+       </font>
+      </property>
+     </widget>
+    </item>
+    <item>
+     <layout class="QHBoxLayout" name="horizontalLayout">
+      <item>
+       <spacer name="horizontalSpacer_2">
+        <property name="orientation">
+         <enum>Qt::Horizontal</enum>
+        </property>
+        <property name="sizeHint" stdset="0">
+         <size>
+          <width>40</width>
+          <height>20</height>
+         </size>
+        </property>
+       </spacer>
+      </item>
+      <item>
+       <widget class="QCheckBox" name="cbPointingTests">
+        <property name="text">
+         <string>Pointing Tests</string>
+        </property>
+       </widget>
+      </item>
+      <item>
+       <spacer name="horizontalSpacer">
+        <property name="orientation">
+         <enum>Qt::Horizontal</enum>
+        </property>
+        <property name="sizeHint" stdset="0">
+         <size>
+          <width>40</width>
+          <height>20</height>
+         </size>
+        </property>
+       </spacer>
+      </item>
+     </layout>
+    </item>
+   </layout>
   </widget>
  </widget>
  <resources/>
diff --git a/map65/libm65/decode0.f90 b/map65/libm65/decode0.f90
index 7401c509a..ba167cddf 100644
--- a/map65/libm65/decode0.f90
+++ b/map65/libm65/decode0.f90
@@ -14,6 +14,7 @@ subroutine decode0(dd,ss,savg,nstandalone)
        mcall3,nkeep,ntol,nxant,nrxlog,nfsample,nxpol,nmode,               &
        nfast,nsave,max_drift,nhsym,mycall,mygrid,hiscall,hisgrid,datetime
   common/early/nhsym1,nhsym2,ldecoded(32768)
+  common/decodes/ndecodes
   data neme0/-99/,mcall3b/1/
   save
 
@@ -62,8 +63,8 @@ subroutine decode0(dd,ss,savg,nstandalone)
   call sec0(1,tdec)
   if(nhsym.eq.nhsym1) write(*,1010) nsum,nsave,nstandalone,nhsym,tdec
 1010 format('<EarlyFinished>',3i4,i6,f6.2)
-  if(nhsym.eq.nhsym2) write(*,1012) nsum,nsave,nstandalone,nhsym,tdec
-1012 format('<DecodeFinished>',3i4,i6,f6.2)
+  if(nhsym.eq.nhsym2) write(*,1012) nsum,nsave,nstandalone,nhsym,tdec,ndecodes
+1012 format('<DecodeFinished>',3i4,i6,f6.2,i5)
   flush(6)
 
   return
diff --git a/map65/libm65/map65a.f90 b/map65/libm65/map65a.f90
index 01c4e54fa..87afa48cd 100644
--- a/map65/libm65/map65a.f90
+++ b/map65/libm65/map65a.f90
@@ -34,12 +34,15 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
   common/c3com/ mcall3a
   common/testcom/ifreq
   common/early/nhsym1,nhsym2,ldecoded(32768)
+  common/decodes/ndecodes
 
   data blank/'                      '/,cm/'#'/
   data shmsg0/'ATT','RO ','RRR','73 '/
   data nfile/0/,nutc0/-999/,nid/0/,ip000/1/,ip001/1/,mousefqso0/-999/
   save
 
+  ndecodes=0
+
 ! Clean start for Q65 at early decode
   if(nhsym.eq.nhsym1 .or. nagain.ne.0) ldecoded=.false.
   if(ndiskdat.eq.1) ldecoded=.false.
@@ -50,7 +53,7 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
   mode65=mod(nmode,10)
   if(mode65.eq.3) mode65=4
   mode_q65=nmode/10
-  nts_jt65=2**(mode65-1)              !JT65 tone separation factor
+  nts_jt65=mode65                     !JT65 tone separation factor
   nts_q65=2**(mode_q65-1)             !Q65 tone separation factor
   xpol=(nxpol.ne.0)
   
@@ -158,7 +161,7 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
            ssmax=1.e30
            call ccf65(ss(1,1,i),nhsym,ssmax,sync1,ipol,jpz,dt,     &
                 flipk,syncshort,snr2,ipol2,dt2)
-           if(dt.lt.-2.6 .or. dt.gt.2.5) sync1=-99.0  !###
+!###           if(dt.lt.-2.6 .or. dt.gt.2.5) sync1=-99.0  !###
            call timer('ccf65   ',1)
            if(mode65.eq.0) syncshort=-99.0     !If "No JT65", don't waste time
 
@@ -410,8 +413,8 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
            if(cand(icand)%iflip.ne.0) cycle    !Do only Q65 candidates here
            if(candec(icand)) cycle             !Skip if already decoded
            freq=cand(icand)%f+nkhz_center-48.0-1.27046
-! If here at nqd=1, do only candidates at mousefqso +/- ntol
-           if(nqd.eq.1 .and. abs(freq-mousefqso).gt.0.001*ntol) cycle
+!###! If here at nqd=1, do only candidates at mousefqso +/- ntol
+!###           if(nqd.eq.1 .and. abs(freq-mousefqso).gt.0.001*ntol) cycle
            ikhz=nint(freq)
            f0=cand(icand)%f
            call timer('q65b    ',0)
@@ -499,6 +502,7 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
            write(26,1014) f0,ndf,ndf0,ndf1,ndf2,dt,npol,nsync1,       &
                 nsync2,nutc,decoded,cp,cmode
 1014       format(f8.3,i5,3i3,f5.1,i4,i3,i4,i5.4,4x,a22,2x,a1,3x,a2)
+           ndecodes=ndecodes+1
            write(21,1100) f0,ndf,dt,npol,nsync2,nutc,decoded,cp,          &
                 cmode(1:1),cmode(2:2)
 1100       format(f8.3,i5,f5.1,2i4,i5.4,2x,a22,2x,a1,3x,a1,1x,a1)
diff --git a/map65/libm65/q65b.f90 b/map65/libm65/q65b.f90
index 3366694d5..92be6528a 100644
--- a/map65/libm65/q65b.f90
+++ b/map65/libm65/q65b.f90
@@ -35,6 +35,7 @@ subroutine q65b(nutc,nqd,nxant,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,xpol, &
   character*1 cp,cmode*2
   common/cacb/ca,cb
   common/early/nhsym1,nhsym2,ldecoded(32768)
+  common/decodes/ndecodes
   data nutc00/-1/,msg00/'                            '/
   save
 
@@ -179,6 +180,7 @@ subroutine q65b(nutc,nqd,nxant,fcenter,nfcal,nfsample,ikhz,mousedf,ntol,xpol, &
 ! to map65_rx.log
      if(nutc.ne.nutc00 .or. msg0(1:28).ne.msg00 .or. freq1.ne.freq1_00) then
 ! Write to file map65_rx.log:
+        ndecodes=ndecodes+1
         write(21,1110)  freq1,ndf,xdt0,npol,nsnr0,nutc,msg0(1:28),cq0
 1110    format(f8.3,i5,f5.1,2i4,i5.4,2x,a28,': A',2x,a3)
         nutc00=nutc
diff --git a/map65/main.cpp b/map65/main.cpp
index 07e1d4c02..0fd3680b2 100644
--- a/map65/main.cpp
+++ b/map65/main.cpp
@@ -19,7 +19,7 @@ int main(int argc, char *argv[])
   QApplication a {argc, argv};
   // Override programs executable basename as application name.
   a.setApplicationName ("MAP65");
-  a.setApplicationVersion ("3.0.0");
+  a.setApplicationVersion ("3.0.1");
   // switch off as we share an Info.plist file with WSJT-X
   a.setAttribute (Qt::AA_DontUseNativeMenuBar);
   MainWindow w;
diff --git a/map65/mainwindow.cpp b/map65/mainwindow.cpp
index 54b84b73a..4ab500f65 100644
--- a/map65/mainwindow.cpp
+++ b/map65/mainwindow.cpp
@@ -520,6 +520,8 @@ void MainWindow::dataSink(int k)
   static int nkhz;
   static int nfsample=96000;
   static int nxpol=0;
+  static int nsec0=0;
+  static int nsum=0;
   static float fgreen;
   static int ndiskdat;
   static int nb;
@@ -529,6 +531,7 @@ void MainWindow::dataSink(int k)
   static float rejectx;
   static float rejecty;
   static float slimit;
+  static double xsum=0.0;
 
   if(m_diskData) {
     ndiskdat=1;
@@ -551,8 +554,22 @@ void MainWindow::dataSink(int k)
            &nfsample, &fgreen, &m_adjustIQ, &m_applyIQcal,
            &m_gainx, &m_gainy, &m_phasex, &m_phasey, &rejectx, &rejecty,
            &px, &py, s, &nkhz, &ihsym, &nzap, &slimit, lstrong);
+
+  int nsec=QDateTime::currentSecsSinceEpoch();
+  if(nsec==nsec0) {
+    xsum+=pow(10.0,0.1*px);
+    nsum+=1;
+  } else {
+    m_xavg=0.0;
+    if(nsum>0) m_xavg=xsum/nsum;
+    xsum=pow(10.0,0.1*px);
+    nsum=1;
+  }
+  nsec0=nsec;
+
   QString t;
   m_pctZap=nzap/178.3;
+  ui->yMeterFrame->setVisible(m_xpol);
   if(m_xpol) {
     lab4->setText (
                   QString {" Rx noise: %1  %2 %3 %% "}
@@ -1119,6 +1136,9 @@ void MainWindow::diskDat()                                   //diskDat()
   //These may be redundant??
   m_diskData=true;
   datcom_.newdat=1;
+  if(m_wide_graph_window->m_bForceCenterFreq) {
+    datcom_.fcenter=m_wide_graph_window->m_dForceCenterFreq;
+  }
 
   if(m_fs96000) hsym=2048.0*96000.0/11025.0;   //Samples per JT65 half-symbol
   if(!m_fs96000) hsym=2048.0*95238.1/11025.0;
@@ -1396,6 +1416,8 @@ void MainWindow::readFromStdout()                             //readFromStdout
       QFile lockFile(m_appDir + "/.lock");
       lockFile.open(QIODevice::ReadWrite);
       if(t.indexOf("<DecodeFinished>") >= 0) {
+        int ndecodes=t.mid(40,5).toInt();
+        lab5->setText(QString::number(ndecodes));
         m_map65RxLog=0;
         m_startAnother=m_loopall;
       }
@@ -1404,6 +1426,8 @@ void MainWindow::readFromStdout()                             //readFromStdout
       return;
     }
 
+    read_log();
+
     if(t.indexOf("!") >= 0) {
       int n=t.length();
       int m=2;
@@ -1688,7 +1712,7 @@ void MainWindow::guiUpdate()
     QDateTime t = QDateTime::currentDateTimeUtc();
     int fQSO=m_wide_graph_window->QSOfreq();
     m_astro_window->astroUpdate(t, m_myGrid, m_hisGrid, fQSO, m_setftx,
-                          m_txFreq, m_azelDir);
+                          m_txFreq, m_azelDir, m_xavg);
     m_setftx=0;
     QString utc = t.date().toString(" yyyy MMM dd \n") + t.time().toString();
     ui->labUTC->setText(utc);
@@ -2344,3 +2368,24 @@ bool MainWindow::isGrid4(QString g)
   if(g.mid(3,1)<'0' or g.mid(3,1)>'9') return false;
   return true;
 }
+
+void MainWindow::read_log()
+{
+  // Update "m_worked" by reading wsjtx.log
+  m_worked.clear();                     //Start from scratch
+  QFile f("wsjtx.log");
+  f.open(QIODevice::ReadOnly);
+  if(f.isOpen()) {
+    QTextStream in(&f);
+    QString line,callsign;
+    for(int i=0; i<99999; i++) {
+      line=in.readLine();
+      if(line.length()<=0) break;
+      callsign=line.mid(40,6);
+      int n=callsign.indexOf(",");
+      if(n>0) callsign=callsign.left(n);
+      m_worked[callsign]=true;
+    }
+    f.close();
+  }
+}
diff --git a/map65/mainwindow.h b/map65/mainwindow.h
index b90683fc7..ebee97403 100644
--- a/map65/mainwindow.h
+++ b/map65/mainwindow.h
@@ -194,12 +194,12 @@ private:
   qint32  m_RxState;
   qint32  m_dB;
 
-
   double  m_fAdd;
   //    double  m_IQamp;
   //    double  m_IQphase;
   double  m_cal570;
   double  m_TxOffset;
+  double  m_xavg;
 
   bool    m_monitoring;
   bool    m_transmitting;
@@ -294,6 +294,7 @@ private:
   void stub();
   bool isGrid4(QString g);
   bool subProcessFailed (QProcess *, int exit_code, QProcess::ExitStatus);
+  void read_log();
 };
 
 extern void getfile(QString fname, bool xpol, int idInt);
diff --git a/widgets/mainwindow.cpp b/widgets/mainwindow.cpp
index 2db7bddf0..ec22876c6 100644
--- a/widgets/mainwindow.cpp
+++ b/widgets/mainwindow.cpp
@@ -90,6 +90,7 @@
 #include "ExportCabrillo.h"
 #include "ui_mainwindow.h"
 #include "moc_mainwindow.cpp"
+#include "Logger.hpp"
 
 #define FCL fortran_charlen_t
 
@@ -155,7 +156,7 @@ extern "C" {
 
   void save_echo_params_(int* ndoptotal, int* ndop, int* nfrit, float* f1, float* fspread, short id2[], int* idir);
 
-  void avecho_( short id2[], int* dop, int* nfrit, int* nauto, int* nqual, float* f1,
+  void avecho_( short id2[], int* dop, int* nfrit, int* nauto, int* navg, int* nqual, float* f1,
                 float* level, float* sigdb, float* snr, float* dfreq,
                 float* width, bool* bDiskData);
 
@@ -208,6 +209,8 @@ QVector<QColor> g_ColorTbl;
 using SpecOp = Configuration::SpecialOperatingActivity;
 
 bool m_displayBand = false;
+bool no_a7_decodes = false;
+bool keep_frequency = false;
 
 namespace
 {
@@ -753,24 +756,6 @@ MainWindow::MainWindow(QDir const& temp_directory, bool multiple,
               }
           });
 
-  // ensure a balanced layout of the mode buttons
-  qreal pointSize = m_config.text_font().pointSizeF();
-  if (pointSize < 11) {
-      ui->houndButton->setMaximumWidth(40);
-      ui->ft8Button->setMaximumWidth(40);
-      ui->ft4Button->setMaximumWidth(40);
-      ui->msk144Button->setMaximumWidth(40);
-      ui->q65Button->setMaximumWidth(40);
-      ui->jt65Button->setMaximumWidth(40);
-  } else {
-      ui->houndButton->setMinimumWidth(50);
-      ui->ft8Button->setMinimumWidth(50);
-      ui->ft4Button->setMinimumWidth(50);
-      ui->msk144Button->setMinimumWidth(50);
-      ui->q65Button->setMinimumWidth(50);
-      ui->jt65Button->setMinimumWidth(50);
-  }
-
   // hook up save WAV file exit handling
   connect (&m_saveWAVWatcher, &QFutureWatcher<QString>::finished, [this] {
       // extract the promise from the future
@@ -1224,6 +1209,7 @@ void MainWindow::writeSettings()
   m_settings->setValue("Blanker",ui->sbNB->value());
   m_settings->setValue("Score",m_score);
   m_settings->setValue("labDXpedText",ui->labDXped->text());
+  m_settings->setValue("EchoAvg",ui->sbEchoAvg->value());
 
   {
     QList<QVariant> coeffs;     // suitable for QSettings
@@ -1357,6 +1343,7 @@ void MainWindow::readSettings()
   ui->actionAuto_Clear_Avg->setChecked (m_settings->value ("AutoClearAvg", false).toBool());
   ui->decodes_splitter->restoreState(m_settings->value("SplitterState").toByteArray());
   ui->sbNB->setValue(m_settings->value("Blanker",0).toInt());
+  ui->sbEchoAvg->setValue(m_settings->value("EchoAvg",10).toInt());
   {
     auto const& coeffs = m_settings->value ("PhaseEqualizationCoefficients"
                                             , QList<QVariant> {0., 0., 0., 0., 0.}).toList ();
@@ -1374,6 +1361,7 @@ void MainWindow::readSettings()
   m_audioThreadPriority = static_cast<QThread::Priority> (m_settings->value ("Audio/ThreadPriority", QThread::TimeCriticalPriority).toInt () % 8);
   m_settings->endGroup ();
 
+  m_specOp=m_config.special_op_id();
   checkMSK144ContestType();
   if(displayMsgAvg) on_actionMessage_averaging_triggered();
   if (displayFoxLog) on_fox_log_action_triggered ();
@@ -1410,10 +1398,35 @@ void MainWindow::set_application_font (QFont const& font)
       QFile sf {sheet};
       if (sf.open (QFile::ReadOnly | QFile::Text))
         {
-          ss = sf.readAll () + ss;
+          QString tmp = sf.readAll();
+          if (tmp != NULL) ss = sf.readAll () + tmp;
+          else qDebug() << "tmp==NULL at sf.readAll";
         }
     }
   qApp->setStyleSheet (ss + "* {" + font_as_stylesheet (font) + '}');
+  // ensure a balanced layout of the mode buttons
+  qreal pointSize = m_config.text_font().pointSizeF();
+  if (pointSize < 11) {
+      ui->houndButton->setMaximumWidth(40);
+      ui->ft8Button->setMaximumWidth(40);
+      ui->ft4Button->setMaximumWidth(40);
+      ui->msk144Button->setMaximumWidth(40);
+      ui->q65Button->setMaximumWidth(40);
+      ui->jt65Button->setMaximumWidth(40);
+      ui->houndButton->setMinimumWidth(0);
+      ui->ft8Button->setMinimumWidth(0);
+      ui->ft4Button->setMinimumWidth(0);
+      ui->msk144Button->setMinimumWidth(0);
+      ui->q65Button->setMinimumWidth(0);
+      ui->jt65Button->setMinimumWidth(0);
+  } else {
+      ui->houndButton->setMinimumWidth(50);
+      ui->ft8Button->setMinimumWidth(50);
+      ui->ft4Button->setMinimumWidth(50);
+      ui->msk144Button->setMinimumWidth(50);
+      ui->q65Button->setMinimumWidth(50);
+      ui->jt65Button->setMinimumWidth(50);
+  }
   for (auto& widget : qApp->topLevelWidgets ())
     {
       widget->updateGeometry ();
@@ -1541,7 +1554,7 @@ void MainWindow::dataSink(qint64 frames)
   if(m_ihsym <=0) return;
   if(ui) ui->signal_meter_widget->setValue(m_px,m_pxmax); // Update thermometer
   if(m_monitoring || m_diskData) {
-    m_wideGraph->dataSink2(s,m_df3,m_ihsym,m_diskData);
+    m_wideGraph->dataSink2(s,m_df3,m_ihsym,m_diskData,m_px);
   }
   if(m_mode=="MSK144") return;
 
@@ -1616,11 +1629,12 @@ void MainWindow::dataSink(qint64 frames)
       echocom_.nclearave=m_nclearave;
       int nDop=m_fAudioShift;
       int nDopTotal=m_fDop;
+      int navg=ui->sbEchoAvg->value();
       if(m_diskData) {
         int idir=-1;
         save_echo_params_(&nDopTotal,&nDop,&nfrit,&f1,&width,dec_data.d2,&idir);
       }
-      avecho_(dec_data.d2,&nDop,&nfrit,&nauto,&nqual,&f1,&xlevel,&sigdb,
+      avecho_(dec_data.d2,&nDop,&nfrit,&nauto,&navg,&nqual,&f1,&xlevel,&sigdb,
           &dBerr,&dfreq,&width,&m_diskData);
       //Don't restart Monitor after an Echo transmission
       if(m_bEchoTxed and !m_auto) {
@@ -1629,7 +1643,7 @@ void MainWindow::dataSink(qint64 frames)
       }
 
       if(m_monitoring or m_auto or m_diskData) {
-        QString t0;
+        QString t0,t1;
         if(m_diskData) {
           t0=t0.asprintf("%06d  ",m_UTCdisk);
         } else {
@@ -1640,17 +1654,20 @@ void MainWindow::dataSink(qint64 frames)
           if(m_auto) isec=isec - isec%6;
           if(!m_auto) isec=isec - isec%3;
           t0=t0.asprintf("%02d%02d%02d  ",ihr,imin,isec);
+          t1=now.toString("yyMMdd_");
         }
         int n=t0.toInt();
         int nsec=((n/10000)*3600) + (((n/100)%100)*60) + (n%100);
-        if(!m_echoRunning) m_echoSec0=nsec;
-        n=(nsec-m_echoSec0 + 864000)%86400;
+        if(!m_echoRunning or echocom_.nsum<2) m_echoSec0=nsec;
+        float hour=n/10000 + ((n/100)%100)/60.0 + (n%100)/3600.0;
         m_echoRunning=true;
         QString t;
-        t = t.asprintf("%6d  %5.2f %7d %7.1f %7d %7d %7d %7.1f %7.1f",n,xlevel,
+        t = t.asprintf("%9.6f  %5.2f %7d %7.1f %7d %7d %7d %7.1f %7.1f",hour,xlevel,
                        nDopTotal,width,echocom_.nsum,nqual,qRound(dfreq),sigdb,dBerr);
         t = t0 + t;
         if (ui) ui->decodedTextBrowser->appendText(t);
+        t=t1+t;
+        write_all("Rx",t);
       }
 
       if(m_echoGraph->isVisible()) m_echoGraph->plotSpec();
@@ -3176,6 +3193,7 @@ void MainWindow::on_ClrAvgButton_clicked()
   if(m_mode=="Echo") {
     echocom_.nsum=0;
     m_echoGraph->clearAvg();
+    m_wideGraph->restartTotalPower();
   } else {
     if(m_msgAvgWidget != NULL) {
       if(m_msgAvgWidget->isVisible()) m_msgAvgWidget->displayAvg("");
@@ -3682,6 +3700,10 @@ void MainWindow::readFromStdout()                             //readFromStdout
           continue;
         }
       }
+
+    // Don't allow a7 decodes during the first period because they can be leftovers from the previous band
+    if (!(no_a7_decodes && line_read.contains("a7"))) {
+
     if (m_mode!="FT8" and m_mode!="FT4" and !m_mode.startsWith ("FST4") and m_mode!="Q65") {
       //Pad 22-char msg to at least 37 chars
       line_read = line_read.left(44) + "              " + line_read.mid(44);
@@ -3748,6 +3770,7 @@ void MainWindow::readFromStdout()                             //readFromStdout
           }
         m_tBlankLine = line_read.left(ntime);
       }
+    }
       if ("FST4W" == m_mode)
         {
           uploadWSPRSpots (true, line_read);
@@ -3797,7 +3820,8 @@ void MainWindow::readFromStdout()                             //readFromStdout
 
           if (m_config.highlight_DXcall () && (m_hisCall!="") && ((decodedtext.string().contains(QRegularExpression {"(\\w+) " + m_hisCall}))
                || (decodedtext.string().contains(QRegularExpression {"(\\w+) <" + m_hisCall +">"}))
-               || (decodedtext.string().contains(QRegularExpression {"<(\\w+)> " + m_hisCall}))))  {
+               || (decodedtext.string().contains(QRegularExpression {"<(\\w+)> " + m_hisCall}))
+               || (decodedtext.string().contains(QRegularExpression {"<...> " + m_hisCall}))))  {
               ui->decodedTextBrowser->highlight_callsign(m_hisCall, QColor(255,0,0), QColor(255,255,255), true); // highlight dxCallEntry
               QTimer::singleShot (500, [=] {                       // repeated highlighting to override JTAlert
                   ui->decodedTextBrowser->highlight_callsign(m_hisCall, QColor(255,0,0), QColor(255,255,255), true);
@@ -4019,7 +4043,8 @@ void MainWindow::readFromStdout()                             //readFromStdout
             if(f.open(QIODevice::ReadOnly | QIODevice::Text)) {
               QTextStream s(&f);
               QString t=s.readAll();
-              m_msgAvgWidget->displayAvg(t);
+              if (t != NULL) m_msgAvgWidget->displayAvg(t);
+              else qDebug() << "tmp==NULL at s.readAll";
             }
           }
         }
@@ -4119,7 +4144,7 @@ void MainWindow::pskPost (DecodedText const& decodedtext)
   }
   int snr = decodedtext.snr();
   Frequency frequency = m_freqNominalPeriod + audioFrequency;   // prevent spotting wrong band
-  if(grid.contains (grid_regexp)) {
+  if(grid.contains (grid_regexp)  || decodedtext.string().contains(" CQ ")) {
 //    qDebug() << "To PSKreporter:" << deCall << grid << frequency << msgmode << snr;
     if (!m_psk_Reporter.addRemoteStation (deCall, grid, frequency, msgmode, snr))
       {
@@ -6148,7 +6173,9 @@ void MainWindow::on_addButton_clicked()                       //Add button
                                               // preserve symlinks
     f1.open (QFile::WriteOnly | QFile::Text); // truncates
     f2.seek (0);
-    f1.write (f2.readAll ());                 // copy contents
+    QByteArray tmp = f2.readAll();
+    if (tmp != (const char*)NULL) f1.write (tmp);                 // copy contents
+    else qDebug() << "tmp==NULL at f1.write";
     f2.remove ();
   }
 }
@@ -6526,6 +6553,7 @@ void MainWindow::displayWidgets(qint64 n)
       (m_config.RTTY_Exchange()=="DX" or m_config.RTTY_Exchange()=="#") );
   }
   if(m_mode=="MSK144") b=SpecOp::EU_VHF==m_specOp;
+  ui->sbEchoAvg->setVisible(m_mode=="Echo");
   ui->sbSerialNumber->setVisible(b);
   m_lastCallsign.clear ();     // ensures Tx5 is updated for new modes
   b=m_mode.startsWith("FST4");
@@ -6634,6 +6662,7 @@ void MainWindow::on_actionFT4_triggered()
   m_wideGraph->setMode(m_mode);
   m_send_RR73=true;
   VHF_features_enabled(bVHF);
+  ui->cbAutoSeq->setChecked(true);
   m_fastGraph->hide();
   m_wideGraph->show();
   ui->rh_decodes_headings_label->setText("  UTC   dB   DT Freq    " + tr ("Message"));
@@ -6740,7 +6769,7 @@ void MainWindow::on_actionFT8_triggered()
     ui->txb5->setEnabled(false);
     ui->txb6->setEnabled(false);
   } else {
-    switch_mode (Modes::FT8);
+    if (!(keep_frequency)) switch_mode (Modes::FT8);
   }
 
   if(m_specOp != SpecOp::HOUND) {
@@ -6951,6 +6980,7 @@ void MainWindow::on_actionQ65_triggered()
   m_mode="Q65";
   ui->actionQ65->setChecked(true);
   switch_mode(Modes::Q65);
+  ui->cbAutoSeq->setChecked(true);
   fast_config(false);
   WSPR_config(false);
   setup_status_bar(true);
@@ -7032,6 +7062,7 @@ void MainWindow::on_actionMSK144_triggered()
   m_toneSpacing=0.0;
   WSPR_config(false);
   VHF_features_enabled(true);
+  ui->cbAutoSeq->setChecked(true);
   m_bFastMode=true;
   m_bFast9=false;
   ui->sbTR->values ({5, 10, 15, 30});
@@ -7108,7 +7139,13 @@ void MainWindow::on_actionWSPR_triggered()
 
 void MainWindow::on_actionEcho_triggered()
 {
+  int nd=int(m_ndepth&3);
   on_actionJT4_triggered();
+// Don't allow decoding depth to be changed just because Echo mode was entered:
+  if(nd==1) ui->actionQuickDecode->setChecked (true);
+  if(nd==2) ui->actionMediumDecode->setChecked (true);
+  if(nd==3) ui->actionDeepestDecode->setChecked (true);
+
   m_mode="Echo";
   ui->actionEcho->setChecked(true);
   m_TRperiod=3.0;
@@ -7131,11 +7168,11 @@ void MainWindow::on_actionEcho_triggered()
   m_bFastMode=false;
   m_bFast9=false;
   WSPR_config(true);
-  ui->lh_decodes_headings_label->setText("  UTC     Tsec  Level  Doppler  Width       N       Q      DF    SNR    dBerr");
+  ui->lh_decodes_headings_label->setText("  UTC      Hour    Level  Doppler  Width       N       Q      DF     SNR    dBerr");
   //                       01234567890123456789012345678901234567
   displayWidgets(nWidgets("00000000000000000010001000000000000000"));
   fast_config(false);
-  if(m_astroWidget) m_astroWidget->selectOwnEcho();
+  ui->sbEchoAvg->values ({1, 2, 5, 10, 20, 50, 100});
   statusChanged();
   monitor(false);
 }
@@ -7455,6 +7492,10 @@ void MainWindow::on_bandComboBox_activated (int index)
 
 void MainWindow::band_changed (Frequency f)
 {
+  // Don't allow a7 decodes during the first period because they can be leftovers from the previous band
+  no_a7_decodes = true;
+  QTimer::singleShot ((int(1500.0*m_TRperiod)), [=] {no_a7_decodes = false;});
+
   // Set the attenuation value if options are checked
   if (m_config.pwrBandTxMemory() && !m_tune) {
     auto const&curBand = ui->bandComboBox->currentText();
@@ -7991,7 +8032,7 @@ void MainWindow::on_outAttenuation_valueChanged (int a)
     tt_str = tr ("Transmit digital gain ");
   }
   tt_str += (a ? QString::number (-dBAttn, 'f', 1) : "0") + "dB";
-  if (!m_block_pwr_tooltip) {
+  if (ui->outAttenuation->hasFocus() && !m_block_pwr_tooltip) {
     QToolTip::showText (QCursor::pos (), tt_str, ui->outAttenuation);
   }
   QString curBand = ui->bandComboBox->currentText();
@@ -9734,45 +9775,55 @@ void MainWindow::write_all(QString txRx, QString message)
   QString t;
   QString msg;
   QString mode_string;
-
-  if (message.size () > 5 && message[4]==' ') {
-     msg=message.mid(4,-1);
-  } else {
-     msg=message.mid(6,-1);
-  }
-
-  if (message.size () > 19 && message[19]=='#') {
-     mode_string="JT65  ";
-  } else if (message.size () > 19 && message[19]=='@') {
-     mode_string="JT9   ";
-  } else if(m_mode=="Q65") {
-    mode_string=mode_label.text();
-  } else {
-     mode_string=m_mode.leftJustified(6,' ');
-  }
-
-  msg=msg.mid(0,15) + msg.mid(18,-1);
-
-  t = t.asprintf("%5d",ui->TxFreqSpinBox->value());
-  if (txRx=="Tx") msg="   0  0.0" + t + " " + message;
-  auto time = QDateTime::currentDateTimeUtc ();
-  if( txRx=="Rx" && !m_bFastMode ) time=m_dateTimeSeqStart;
-
-  t = t.asprintf("%10.3f ",m_freqNominalPeriod/1.e6);   // prevent writing of wrong frequencies
-  if (m_diskData) {
-    if (m_fileDateTime.size()==11) {
-      line=m_fileDateTime + "  " + t + txRx + " " + mode_string + msg;
-    } else {
-      line=m_fileDateTime + t + txRx + " " + mode_string + msg;
-    } 
-  } else {
-    line=time.toString("yyMMdd_hhmmss") + t + txRx + " " + mode_string + msg;
-  }
-
   QString file_name="ALL.TXT";
-  if (ui->actionSplit_ALL_TXT_yearly->isChecked()) file_name=(time.toString("yyyy") + "-" + "ALL.TXT");
-  if (ui->actionSplit_ALL_TXT_monthly->isChecked()) file_name=(time.toString("yyyy-MM") + "-" + "ALL.TXT");
-  if (m_mode=="WSPR") file_name="ALL_WSPR.TXT";
+
+  if(m_mode!="Echo") {
+    if (message.size () > 5 && message[4]==' ') {
+      msg=message.mid(4,-1);
+    } else {
+      msg=message.mid(6,-1);
+    }
+
+    if (message.size () > 19 && message[19]=='#') {
+      mode_string="JT65  ";
+    } else if (message.size () > 19 && message[19]=='@') {
+      mode_string="JT9   ";
+    } else if(m_mode=="Q65") {
+      mode_string=mode_label.text();
+    } else {
+      mode_string=m_mode.leftJustified(6,' ');
+    }
+
+    msg=msg.mid(0,15) + msg.mid(18,-1);
+
+    t = t.asprintf("%5d",ui->TxFreqSpinBox->value());
+    if (txRx=="Tx") msg="   0  0.0" + t + " " + message;
+    auto time = QDateTime::currentDateTimeUtc ();
+    if( txRx=="Rx" && !m_bFastMode ) time=m_dateTimeSeqStart;
+
+    if (txRx=="Rx") {
+       t = t.asprintf("%10.3f ",m_freqNominalPeriod/1.e6);   // prevent writing of wrong frequencies
+    } else {
+       t = t.asprintf("%10.3f ",m_freqNominal/1.e6);
+    }
+    if (m_diskData) {
+      if (m_fileDateTime.size()==11) {
+        line=m_fileDateTime + "  " + t + txRx + " " + mode_string + msg;
+      } else {
+        line=m_fileDateTime + t + txRx + " " + mode_string + msg;
+      }
+    } else {
+      line=time.toString("yyMMdd_hhmmss") + t + txRx + " " + mode_string + msg;
+    }
+
+    if (ui->actionSplit_ALL_TXT_yearly->isChecked()) file_name=(time.toString("yyyy") + "-" + "ALL.TXT");
+    if (ui->actionSplit_ALL_TXT_monthly->isChecked()) file_name=(time.toString("yyyy-MM") + "-" + "ALL.TXT");
+    if (m_mode=="WSPR") file_name="ALL_WSPR.TXT";
+  } else {
+    file_name="all_echo.txt";
+    line=message;
+  }
+
   QFile f{m_config.writeable_data_dir().absoluteFilePath(file_name)};
   if (f.open(QIODevice::WriteOnly | QIODevice::Text | QIODevice::Append)) {
     QTextStream out(&f);
@@ -9966,6 +10017,8 @@ void MainWindow::on_houndButton_clicked (bool checked)
   } else {
     ui->houndButton->setStyleSheet("");
     m_config.setSpecial_None();
+    keep_frequency = true;
+    QTimer::singleShot (250, [=] {keep_frequency = false;});
   }
   m_specOp=m_config.special_op_id();
   on_actionFT8_triggered();
@@ -10025,26 +10078,3 @@ void MainWindow::on_jt65Button_clicked()
     }
     on_actionJT65_triggered();
 }
-
-void MainWindow::on_actionCopy_to_WSJTX_txt_triggered()
-{
-  static QFile f {QDir {QStandardPaths::writableLocation (QStandardPaths::DataLocation)}.absoluteFilePath ("WSJT-X.txt")};
-  if(!f.open(QIODevice::Text | QIODevice::WriteOnly)) {
-    MessageBox::warning_message (this, tr ("WSJT-X.txt file error"),
-                                 tr ("Cannot open \"%1\" for writing").arg (f.fileName ()),
-                                 tr ("Error: %1").arg (f.errorString ()));
-  } else {
-    QString t=ui->decodedTextBrowser->toPlainText();
-
-    QTextStream out(&f);
-    out << t <<
-#if QT_VERSION < QT_VERSION_CHECK(5, 15, 0)
-                 endl
-#else
-                 Qt::endl
-#endif
-                 ;
-    f.close();
-  }
-}
-
diff --git a/widgets/mainwindow.h b/widgets/mainwindow.h
index 9f12f7971..e424a6ed8 100644
--- a/widgets/mainwindow.h
+++ b/widgets/mainwindow.h
@@ -173,7 +173,6 @@ private slots:
   void on_actionOpen_next_in_directory_triggered();
   void on_actionDecode_remaining_files_in_directory_triggered();
   void on_actionDelete_all_wav_files_in_SaveDir_triggered();
-  void on_actionCopy_to_WSJTX_txt_triggered();
   void on_actionOpen_log_directory_triggered ();
   void on_actionNone_triggered();
   void on_actionSave_all_triggered();
diff --git a/widgets/mainwindow.ui b/widgets/mainwindow.ui
index c275a70e8..733dc4dc9 100644
--- a/widgets/mainwindow.ui
+++ b/widgets/mainwindow.ui
@@ -6,7 +6,7 @@
    <rect>
     <x>0</x>
     <y>0</y>
-    <width>893</width>
+    <width>901</width>
     <height>665</height>
    </rect>
   </property>
@@ -36,7 +36,6 @@
           <property name="font">
            <font>
             <pointsize>10</pointsize>
-            <weight>50</weight>
             <bold>false</bold>
            </font>
           </property>
@@ -180,7 +179,6 @@
           <property name="font">
            <font>
             <pointsize>10</pointsize>
-            <weight>50</weight>
             <bold>false</bold>
            </font>
           </property>
@@ -326,7 +324,7 @@
         <number>0</number>
        </property>
        <item>
-        <layout class="QHBoxLayout" name="horizontalLayout_2" stretch="0,2,2,2,2,2,2,2,2,2,1">
+        <layout class="QHBoxLayout" name="horizontalLayout_2" stretch="0,2,2,2,2,2,0,2,2,2,2,1">
          <item>
           <widget class="QCheckBox" name="cbCQonly">
            <property name="text">
@@ -435,6 +433,22 @@
            </property>
           </widget>
          </item>
+         <item>
+          <widget class="HintedSpinBox" name="sbEchoAvg">
+           <property name="prefix">
+            <string>Avg </string>
+           </property>
+           <property name="minimum">
+            <number>1</number>
+           </property>
+           <property name="maximum">
+            <number>100</number>
+           </property>
+           <property name="value">
+            <number>10</number>
+           </property>
+          </widget>
+         </item>
          <item>
           <widget class="QPushButton" name="DecodeButton">
            <property name="minimumSize">
@@ -560,54 +574,418 @@
         </layout>
        </item>
        <item>
-        <layout class="QGridLayout" name="gridLayout_5" rowstretch="1,0,0" columnstretch="0,0,0,1,3,0">
-         <item row="0" column="5">
-          <widget class="QLabel" name="label">
-           <property name="text">
-            <string> Pwr</string>
-           </property>
-          </widget>
-         </item>
-         <item row="2" column="2" colspan="2">
-          <widget class="QLabel" name="labUTC">
+        <layout class="QGridLayout" name="gridLayout_5" rowstretch="1,0,0" columnstretch="0,0,0,0,1,1,5,0">
+         <item row="1" column="4" colspan="2">
+          <widget class="QWidget" name="DX_controls_widget" native="true">
            <property name="sizePolicy">
             <sizepolicy hsizetype="Preferred" vsizetype="Maximum">
              <horstretch>0</horstretch>
              <verstretch>0</verstretch>
             </sizepolicy>
            </property>
-           <property name="styleSheet">
-            <string notr="true">QLabel {
-  font-family: MS Shell Dlg 2;
-  font-size: 16pt;
-  background-color : black;
-  color : yellow;
-}</string>
+           <layout class="QGridLayout" name="gridLayout_2" columnstretch="2,1">
+            <property name="leftMargin">
+             <number>0</number>
+            </property>
+            <property name="topMargin">
+             <number>0</number>
+            </property>
+            <property name="rightMargin">
+             <number>0</number>
+            </property>
+            <property name="bottomMargin">
+             <number>0</number>
+            </property>
+            <item row="0" column="0">
+             <widget class="QLabel" name="label_3">
+              <property name="palette">
+               <palette>
+                <active>
+                 <colorrole role="Base">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>252</red>
+                    <green>252</green>
+                    <blue>252</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                 <colorrole role="Window">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>159</red>
+                    <green>175</green>
+                    <blue>213</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                </active>
+                <inactive>
+                 <colorrole role="Base">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>252</red>
+                    <green>252</green>
+                    <blue>252</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                 <colorrole role="Window">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>159</red>
+                    <green>175</green>
+                    <blue>213</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                </inactive>
+                <disabled>
+                 <colorrole role="Base">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>159</red>
+                    <green>175</green>
+                    <blue>213</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                 <colorrole role="Window">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>159</red>
+                    <green>175</green>
+                    <blue>213</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                </disabled>
+               </palette>
+              </property>
+              <property name="autoFillBackground">
+               <bool>true</bool>
+              </property>
+              <property name="text">
+               <string>DX Call</string>
+              </property>
+              <property name="alignment">
+               <set>Qt::AlignCenter</set>
+              </property>
+              <property name="margin">
+               <number>5</number>
+              </property>
+              <property name="indent">
+               <number>2</number>
+              </property>
+              <property name="buddy">
+               <cstring>dxCallEntry</cstring>
+              </property>
+             </widget>
+            </item>
+            <item row="0" column="1">
+             <widget class="QLabel" name="label_4">
+              <property name="palette">
+               <palette>
+                <active>
+                 <colorrole role="Base">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>252</red>
+                    <green>252</green>
+                    <blue>252</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                 <colorrole role="Window">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>159</red>
+                    <green>175</green>
+                    <blue>213</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                </active>
+                <inactive>
+                 <colorrole role="Base">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>252</red>
+                    <green>252</green>
+                    <blue>252</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                 <colorrole role="Window">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>159</red>
+                    <green>175</green>
+                    <blue>213</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                </inactive>
+                <disabled>
+                 <colorrole role="Base">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>159</red>
+                    <green>175</green>
+                    <blue>213</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                 <colorrole role="Window">
+                  <brush brushstyle="SolidPattern">
+                   <color alpha="255">
+                    <red>159</red>
+                    <green>175</green>
+                    <blue>213</blue>
+                   </color>
+                  </brush>
+                 </colorrole>
+                </disabled>
+               </palette>
+              </property>
+              <property name="autoFillBackground">
+               <bool>true</bool>
+              </property>
+              <property name="text">
+               <string>DX Grid</string>
+              </property>
+              <property name="alignment">
+               <set>Qt::AlignCenter</set>
+              </property>
+              <property name="margin">
+               <number>5</number>
+              </property>
+              <property name="indent">
+               <number>2</number>
+              </property>
+              <property name="buddy">
+               <cstring>dxGridEntry</cstring>
+              </property>
+             </widget>
+            </item>
+            <item row="1" column="0">
+             <widget class="QLineEdit" name="dxCallEntry">
+              <property name="sizePolicy">
+               <sizepolicy hsizetype="Preferred" vsizetype="Fixed">
+                <horstretch>0</horstretch>
+                <verstretch>0</verstretch>
+               </sizepolicy>
+              </property>
+              <property name="toolTip">
+               <string>Callsign of station to be worked</string>
+              </property>
+              <property name="maxLength">
+               <number>11</number>
+              </property>
+              <property name="alignment">
+               <set>Qt::AlignCenter</set>
+              </property>
+             </widget>
+            </item>
+            <item row="1" column="1">
+             <widget class="QLineEdit" name="dxGridEntry">
+              <property name="sizePolicy">
+               <sizepolicy hsizetype="Preferred" vsizetype="Fixed">
+                <horstretch>0</horstretch>
+                <verstretch>0</verstretch>
+               </sizepolicy>
+              </property>
+              <property name="toolTip">
+               <string>Locator of station to be worked</string>
+              </property>
+              <property name="text">
+               <string>`</string>
+              </property>
+              <property name="maxLength">
+               <number>6</number>
+              </property>
+              <property name="alignment">
+               <set>Qt::AlignCenter</set>
+              </property>
+             </widget>
+            </item>
+            <item row="2" column="0" colspan="2">
+             <layout class="QGridLayout" name="gridLayout_4">
+              <item row="1" column="0">
+               <widget class="QPushButton" name="lookupButton">
+                <property name="toolTip">
+                 <string>Search for callsign in database</string>
+                </property>
+                <property name="text">
+                 <string>&amp;Lookup</string>
+                </property>
+               </widget>
+              </item>
+              <item row="1" column="1">
+               <widget class="QPushButton" name="addButton">
+                <property name="toolTip">
+                 <string>Add callsign and locator to database</string>
+                </property>
+                <property name="text">
+                 <string>Add</string>
+                </property>
+               </widget>
+              </item>
+              <item row="0" column="0" colspan="2">
+               <widget class="QLabel" name="labAz">
+                <property name="autoFillBackground">
+                 <bool>true</bool>
+                </property>
+                <property name="text">
+                 <string>Az: 251     16553 km</string>
+                </property>
+                <property name="alignment">
+                 <set>Qt::AlignCenter</set>
+                </property>
+                <property name="indent">
+                 <number>4</number>
+                </property>
+               </widget>
+              </item>
+             </layout>
+            </item>
+           </layout>
+          </widget>
+         </item>
+         <item row="1" column="7" rowspan="2">
+          <widget class="QSlider" name="outAttenuation">
+           <property name="toolTip">
+            <string>Adjust Tx audio level</string>
            </property>
-           <property name="frameShape">
-            <enum>QFrame::StyledPanel</enum>
+           <property name="maximum">
+            <number>450</number>
            </property>
-           <property name="frameShadow">
-            <enum>QFrame::Sunken</enum>
-           </property>
-           <property name="lineWidth">
-            <number>2</number>
-           </property>
-           <property name="midLineWidth">
+           <property name="value">
             <number>0</number>
            </property>
-           <property name="text">
-            <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p align=&quot;center&quot;&gt; 2015 Jun 17 &lt;/p&gt;&lt;p align=&quot;center&quot;&gt; 01:23:45 &lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
+           <property name="orientation">
+            <enum>Qt::Vertical</enum>
            </property>
-           <property name="alignment">
-            <set>Qt::AlignCenter</set>
+           <property name="invertedAppearance">
+            <bool>true</bool>
            </property>
-           <property name="margin">
-            <number>5</number>
+           <property name="invertedControls">
+            <bool>true</bool>
+           </property>
+           <property name="tickPosition">
+            <enum>QSlider::TicksBelow</enum>
+           </property>
+           <property name="tickInterval">
+            <number>50</number>
            </property>
           </widget>
          </item>
-         <item row="0" column="4" rowspan="3">
+         <item row="0" column="7">
+          <widget class="QLabel" name="label">
+           <property name="text">
+            <string> Pwr</string>
+           </property>
+          </widget>
+         </item>
+         <item row="1" column="2" rowspan="2">
+          <layout class="QVBoxLayout" name="verticalLayout_11">
+           <property name="spacing">
+            <number>6</number>
+           </property>
+           <item>
+            <widget class="QSpinBox" name="sbNB">
+             <property name="sizePolicy">
+              <sizepolicy hsizetype="MinimumExpanding" vsizetype="Fixed">
+               <horstretch>0</horstretch>
+               <verstretch>0</verstretch>
+              </sizepolicy>
+             </property>
+             <property name="maximumSize">
+              <size>
+               <width>100</width>
+               <height>16777215</height>
+              </size>
+             </property>
+             <property name="alignment">
+              <set>Qt::AlignCenter</set>
+             </property>
+             <property name="suffix">
+              <string>  %</string>
+             </property>
+             <property name="prefix">
+              <string>NB  </string>
+             </property>
+             <property name="minimum">
+              <number>-2</number>
+             </property>
+             <property name="maximum">
+              <number>25</number>
+             </property>
+            </widget>
+           </item>
+           <item>
+            <layout class="QHBoxLayout" name="horizontalLayout_3">
+             <property name="spacing">
+              <number>0</number>
+             </property>
+             <item>
+              <widget class="SignalMeter" name="signal_meter_widget">
+               <property name="sizePolicy">
+                <sizepolicy hsizetype="Minimum" vsizetype="MinimumExpanding">
+                 <horstretch>0</horstretch>
+                 <verstretch>0</verstretch>
+                </sizepolicy>
+               </property>
+               <property name="minimumSize">
+                <size>
+                 <width>0</width>
+                 <height>0</height>
+                </size>
+               </property>
+               <property name="maximumSize">
+                <size>
+                 <width>100</width>
+                 <height>16777215</height>
+                </size>
+               </property>
+               <property name="toolTip">
+                <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p&gt;30dB recommended when only noise present&lt;br/&gt;Green when good&lt;br/&gt;Red when clipping may occur&lt;br/&gt;Yellow when too low&lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
+               </property>
+               <property name="accessibleName">
+                <string>Rx Signal</string>
+               </property>
+               <property name="accessibleDescription">
+                <string>30dB recommended when only noise present
+Green when good
+Red when clipping may occur
+Yellow when too low</string>
+               </property>
+               <property name="frameShape">
+                <enum>QFrame::Panel</enum>
+               </property>
+               <property name="frameShadow">
+                <enum>QFrame::Sunken</enum>
+               </property>
+              </widget>
+             </item>
+             <item>
+              <spacer name="horizontalSpacer">
+               <property name="orientation">
+                <enum>Qt::Horizontal</enum>
+               </property>
+               <property name="sizeHint" stdset="0">
+                <size>
+                 <width>0</width>
+                 <height>20</height>
+                </size>
+               </property>
+              </spacer>
+             </item>
+            </layout>
+           </item>
+          </layout>
+         </item>
+         <item row="0" column="6" rowspan="3">
           <widget class="QStackedWidget" name="controls_stack_widget">
            <property name="sizePolicy">
             <sizepolicy hsizetype="MinimumExpanding" vsizetype="Preferred">
@@ -834,7 +1212,7 @@ When not checked you can view the calibration results.</string>
                     <item>
                      <widget class="QComboBox" name="respondComboBox">
                       <property name="toolTip">
-                       <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p&gt;Select &lt;span style=&quot; font-weight:600;&quot;&gt;CQ: First&lt;/span&gt; to respond automatically to the first decoded reply to your CQ. &lt;/p&gt;&lt;p&gt;Select &lt;span style=&quot; font-weight:600;&quot;&gt;CQ: Max Pts&lt;/span&gt; to respond automatically to the reply yielding most points in the ARRL International Digital Contest.&lt;/p&gt;&lt;p&gt;Select &lt;span style=&quot; font-weight:600;&quot;&gt;CQ: None&lt;/span&gt; to choose callers manually.&lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
+                       <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p&gt;Select &lt;span style=&quot; font-weight:600;&quot;&gt;CQ: First&lt;/span&gt; to respond automatically to the first decoded reply to your CQ. &lt;/p&gt;&lt;p&gt;Select &lt;span style=&quot; font-weight:600;&quot;&gt;CQ: Max Dist&lt;/span&gt; to respond automatically to the reply yielding most points in the ARRL International Digital Contest.&lt;/p&gt;&lt;p&gt;Select &lt;span style=&quot; font-weight:600;&quot;&gt;CQ: None&lt;/span&gt; to choose callers manually.&lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
                       </property>
                       <property name="currentText">
                        <string/>
@@ -1596,9 +1974,6 @@ list. The list can be maintained in Settings (F2).</string>
                         <property name="insertPolicy">
                          <enum>QComboBox::InsertAtBottom</enum>
                         </property>
-                        <property name="sizeAdjustPolicy">
-                         <enum>QComboBox::AdjustToMinimumContentsLength</enum>
-                        </property>
                        </widget>
                       </item>
                       <item row="5" column="1">
@@ -2392,445 +2767,7 @@ Double-click to reset to the standard 73 message</string>
            </widget>
           </widget>
          </item>
-         <item row="0" column="0">
-          <widget class="BandComboBox" name="bandComboBox">
-           <property name="maximumSize">
-            <size>
-             <width>100</width>
-             <height>16777215</height>
-            </size>
-           </property>
-           <property name="toolTip">
-            <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p&gt;Select operating band or enter frequency in MHz or enter kHz increment followed by k.&lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
-           </property>
-           <property name="accessibleName">
-            <string>Frequency entry</string>
-           </property>
-           <property name="accessibleDescription">
-            <string>Select operating band or enter frequency in MHz or enter kHz increment followed by k.</string>
-           </property>
-           <property name="editable">
-            <bool>true</bool>
-           </property>
-           <property name="insertPolicy">
-            <enum>QComboBox::NoInsert</enum>
-           </property>
-           <property name="sizeAdjustPolicy">
-            <enum>QComboBox::AdjustToMinimumContentsLengthWithIcon</enum>
-           </property>
-          </widget>
-         </item>
-         <item row="1" column="0" rowspan="2">
-          <layout class="QVBoxLayout" name="verticalLayout_11">
-           <item>
-            <widget class="QSpinBox" name="sbNB">
-             <property name="maximumSize">
-              <size>
-               <width>100</width>
-               <height>16777215</height>
-              </size>
-             </property>
-             <property name="alignment">
-              <set>Qt::AlignCenter</set>
-             </property>
-             <property name="suffix">
-              <string>  %</string>
-             </property>
-             <property name="prefix">
-              <string>NB  </string>
-             </property>
-             <property name="minimum">
-              <number>-2</number>
-             </property>
-             <property name="maximum">
-              <number>25</number>
-             </property>
-            </widget>
-           </item>
-           <item>
-            <widget class="SignalMeter" name="signal_meter_widget">
-             <property name="sizePolicy">
-              <sizepolicy hsizetype="MinimumExpanding" vsizetype="MinimumExpanding">
-               <horstretch>0</horstretch>
-               <verstretch>0</verstretch>
-              </sizepolicy>
-             </property>
-             <property name="maximumSize">
-              <size>
-               <width>100</width>
-               <height>16777215</height>
-              </size>
-             </property>
-             <property name="toolTip">
-              <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p&gt;30dB recommended when only noise present&lt;br/&gt;Green when good&lt;br/&gt;Red when clipping may occur&lt;br/&gt;Yellow when too low&lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
-             </property>
-             <property name="accessibleName">
-              <string>Rx Signal</string>
-             </property>
-             <property name="accessibleDescription">
-              <string>30dB recommended when only noise present
-Green when good
-Red when clipping may occur
-Yellow when too low</string>
-             </property>
-             <property name="frameShape">
-              <enum>QFrame::Panel</enum>
-             </property>
-             <property name="frameShadow">
-              <enum>QFrame::Sunken</enum>
-             </property>
-            </widget>
-           </item>
-          </layout>
-         </item>
-         <item row="1" column="2" colspan="2">
-          <widget class="QWidget" name="DX_controls_widget" native="true">
-           <property name="sizePolicy">
-            <sizepolicy hsizetype="Preferred" vsizetype="Maximum">
-             <horstretch>0</horstretch>
-             <verstretch>0</verstretch>
-            </sizepolicy>
-           </property>
-           <layout class="QGridLayout" name="gridLayout_2" columnstretch="2,1">
-            <property name="leftMargin">
-             <number>0</number>
-            </property>
-            <property name="topMargin">
-             <number>0</number>
-            </property>
-            <property name="rightMargin">
-             <number>0</number>
-            </property>
-            <property name="bottomMargin">
-             <number>0</number>
-            </property>
-            <item row="0" column="0">
-             <widget class="QLabel" name="label_3">
-              <property name="palette">
-               <palette>
-                <active>
-                 <colorrole role="Base">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>252</red>
-                    <green>252</green>
-                    <blue>252</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                 <colorrole role="Window">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>159</red>
-                    <green>175</green>
-                    <blue>213</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                </active>
-                <inactive>
-                 <colorrole role="Base">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>252</red>
-                    <green>252</green>
-                    <blue>252</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                 <colorrole role="Window">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>159</red>
-                    <green>175</green>
-                    <blue>213</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                </inactive>
-                <disabled>
-                 <colorrole role="Base">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>159</red>
-                    <green>175</green>
-                    <blue>213</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                 <colorrole role="Window">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>159</red>
-                    <green>175</green>
-                    <blue>213</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                </disabled>
-               </palette>
-              </property>
-              <property name="autoFillBackground">
-               <bool>true</bool>
-              </property>
-              <property name="text">
-               <string>DX Call</string>
-              </property>
-              <property name="alignment">
-               <set>Qt::AlignCenter</set>
-              </property>
-              <property name="margin">
-               <number>5</number>
-              </property>
-              <property name="indent">
-               <number>2</number>
-              </property>
-              <property name="buddy">
-               <cstring>dxCallEntry</cstring>
-              </property>
-             </widget>
-            </item>
-            <item row="0" column="1">
-             <widget class="QLabel" name="label_4">
-              <property name="palette">
-               <palette>
-                <active>
-                 <colorrole role="Base">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>252</red>
-                    <green>252</green>
-                    <blue>252</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                 <colorrole role="Window">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>159</red>
-                    <green>175</green>
-                    <blue>213</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                </active>
-                <inactive>
-                 <colorrole role="Base">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>252</red>
-                    <green>252</green>
-                    <blue>252</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                 <colorrole role="Window">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>159</red>
-                    <green>175</green>
-                    <blue>213</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                </inactive>
-                <disabled>
-                 <colorrole role="Base">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>159</red>
-                    <green>175</green>
-                    <blue>213</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                 <colorrole role="Window">
-                  <brush brushstyle="SolidPattern">
-                   <color alpha="255">
-                    <red>159</red>
-                    <green>175</green>
-                    <blue>213</blue>
-                   </color>
-                  </brush>
-                 </colorrole>
-                </disabled>
-               </palette>
-              </property>
-              <property name="autoFillBackground">
-               <bool>true</bool>
-              </property>
-              <property name="text">
-               <string>DX Grid</string>
-              </property>
-              <property name="alignment">
-               <set>Qt::AlignCenter</set>
-              </property>
-              <property name="margin">
-               <number>5</number>
-              </property>
-              <property name="indent">
-               <number>2</number>
-              </property>
-              <property name="buddy">
-               <cstring>dxGridEntry</cstring>
-              </property>
-             </widget>
-            </item>
-            <item row="1" column="0">
-             <widget class="QLineEdit" name="dxCallEntry">
-              <property name="sizePolicy">
-               <sizepolicy hsizetype="Preferred" vsizetype="Fixed">
-                <horstretch>0</horstretch>
-                <verstretch>0</verstretch>
-               </sizepolicy>
-              </property>
-              <property name="toolTip">
-               <string>Callsign of station to be worked</string>
-              </property>
-              <property name="maxLength">
-               <number>11</number>
-              </property>
-              <property name="alignment">
-               <set>Qt::AlignCenter</set>
-              </property>
-             </widget>
-            </item>
-            <item row="1" column="1">
-             <widget class="QLineEdit" name="dxGridEntry">
-              <property name="sizePolicy">
-               <sizepolicy hsizetype="Preferred" vsizetype="Fixed">
-                <horstretch>0</horstretch>
-                <verstretch>0</verstretch>
-               </sizepolicy>
-              </property>
-              <property name="toolTip">
-               <string>Locator of station to be worked</string>
-              </property>
-              <property name="text">
-               <string>`</string>
-              </property>
-              <property name="maxLength">
-               <number>6</number>
-              </property>
-              <property name="alignment">
-               <set>Qt::AlignCenter</set>
-              </property>
-             </widget>
-            </item>
-            <item row="2" column="0" colspan="2">
-             <layout class="QGridLayout" name="gridLayout_4">
-              <item row="1" column="0">
-               <widget class="QPushButton" name="lookupButton">
-                <property name="toolTip">
-                 <string>Search for callsign in database</string>
-                </property>
-                <property name="text">
-                 <string>&amp;Lookup</string>
-                </property>
-               </widget>
-              </item>
-              <item row="1" column="1">
-               <widget class="QPushButton" name="addButton">
-                <property name="toolTip">
-                 <string>Add callsign and locator to database</string>
-                </property>
-                <property name="text">
-                 <string>Add</string>
-                </property>
-               </widget>
-              </item>
-              <item row="0" column="0" colspan="2">
-               <widget class="QLabel" name="labAz">
-                <property name="autoFillBackground">
-                 <bool>true</bool>
-                </property>
-                <property name="text">
-                 <string>Az: 251     16553 km</string>
-                </property>
-                <property name="alignment">
-                 <set>Qt::AlignCenter</set>
-                </property>
-                <property name="indent">
-                 <number>4</number>
-                </property>
-               </widget>
-              </item>
-             </layout>
-            </item>
-           </layout>
-          </widget>
-         </item>
-         <item row="1" column="5" rowspan="2">
-          <widget class="QSlider" name="outAttenuation">
-           <property name="toolTip">
-            <string>Adjust Tx audio level</string>
-           </property>
-           <property name="maximum">
-            <number>450</number>
-           </property>
-           <property name="value">
-            <number>0</number>
-           </property>
-           <property name="orientation">
-            <enum>Qt::Vertical</enum>
-           </property>
-           <property name="invertedAppearance">
-            <bool>true</bool>
-           </property>
-           <property name="invertedControls">
-            <bool>true</bool>
-           </property>
-           <property name="tickPosition">
-            <enum>QSlider::TicksBelow</enum>
-           </property>
-           <property name="tickInterval">
-            <number>50</number>
-           </property>
-          </widget>
-         </item>
-         <item row="0" column="1" alignment="Qt::AlignHCenter|Qt::AlignVCenter">
-          <widget class="QPushButton" name="readFreq">
-           <property name="enabled">
-            <bool>false</bool>
-           </property>
-           <property name="toolTip">
-            <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p&gt;If orange or red there has been a rig control failure, click to reset and read the dial frequency.  S implies split mode.&lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
-           </property>
-           <property name="accessibleDescription">
-            <string>If orange or red there has been a rig control failure, click to reset and read the dial frequency. S implies split mode.</string>
-           </property>
-           <property name="styleSheet">
-            <string notr="true">QPushButton {
- font-family: helvetica;
- font-size: 9pt;
- font-weight: bold;
- background-color: white;
- color: black;
- border-style: solid;
- border-width:1px;
- border-radius:10px;
- border-color: gray;
- max-width:20px;
- max-height:20px;
- min-width:20px;
- min-height:20px;
-}
-QPushButton[state=&quot;error&quot;] {
- background-color: red;
-}
-QPushButton[state=&quot;warning&quot;] {
- background-color: orange;
-}
-QPushButton[state=&quot;ok&quot;] {
- background-color: #00ff00;
-}</string>
-           </property>
-           <property name="text">
-            <string>?</string>
-           </property>
-          </widget>
-         </item>
-         <item row="0" column="2" colspan="2">
+         <item row="0" column="4" colspan="2">
           <widget class="QLabel" name="labDialFreq">
            <property name="sizePolicy">
             <sizepolicy hsizetype="Preferred" vsizetype="Maximum">
@@ -2863,7 +2800,7 @@ QLabel[oob=&quot;true&quot;] {
            </property>
           </widget>
          </item>
-         <item row="1" column="1" rowspan="2">
+         <item row="1" column="3" rowspan="2">
           <layout class="QVBoxLayout" name="verticalLayout_15">
            <item>
             <widget class="QPushButton" name="houndButton">
@@ -3002,6 +2939,131 @@ QLabel[oob=&quot;true&quot;] {
            </item>
           </layout>
          </item>
+         <item row="2" column="4" colspan="2">
+          <widget class="QLabel" name="labUTC">
+           <property name="sizePolicy">
+            <sizepolicy hsizetype="Preferred" vsizetype="Maximum">
+             <horstretch>0</horstretch>
+             <verstretch>0</verstretch>
+            </sizepolicy>
+           </property>
+           <property name="styleSheet">
+            <string notr="true">QLabel {
+  font-family: MS Shell Dlg 2;
+  font-size: 16pt;
+  background-color : black;
+  color : yellow;
+}</string>
+           </property>
+           <property name="frameShape">
+            <enum>QFrame::StyledPanel</enum>
+           </property>
+           <property name="frameShadow">
+            <enum>QFrame::Sunken</enum>
+           </property>
+           <property name="lineWidth">
+            <number>2</number>
+           </property>
+           <property name="midLineWidth">
+            <number>0</number>
+           </property>
+           <property name="text">
+            <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p align=&quot;center&quot;&gt; 2015 Jun 17 &lt;/p&gt;&lt;p align=&quot;center&quot;&gt; 01:23:45 &lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
+           </property>
+           <property name="alignment">
+            <set>Qt::AlignCenter</set>
+           </property>
+           <property name="margin">
+            <number>5</number>
+           </property>
+          </widget>
+         </item>
+         <item row="0" column="2" colspan="2">
+          <layout class="QHBoxLayout" name="horizontalLayout_16" stretch="1,0">
+           <item>
+            <widget class="BandComboBox" name="bandComboBox">
+             <property name="sizePolicy">
+              <sizepolicy hsizetype="MinimumExpanding" vsizetype="Fixed">
+               <horstretch>0</horstretch>
+               <verstretch>0</verstretch>
+              </sizepolicy>
+             </property>
+             <property name="minimumSize">
+              <size>
+               <width>0</width>
+               <height>0</height>
+              </size>
+             </property>
+             <property name="maximumSize">
+              <size>
+               <width>16777215</width>
+               <height>16777215</height>
+              </size>
+             </property>
+             <property name="toolTip">
+              <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p&gt;Select operating band or enter frequency in MHz or enter kHz increment followed by k.&lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
+             </property>
+             <property name="accessibleName">
+              <string>Frequency entry</string>
+             </property>
+             <property name="accessibleDescription">
+              <string>Select operating band or enter frequency in MHz or enter kHz increment followed by k.</string>
+             </property>
+             <property name="editable">
+              <bool>true</bool>
+             </property>
+             <property name="insertPolicy">
+              <enum>QComboBox::NoInsert</enum>
+             </property>
+             <property name="sizeAdjustPolicy">
+              <enum>QComboBox::AdjustToMinimumContentsLengthWithIcon</enum>
+             </property>
+            </widget>
+           </item>
+           <item>
+            <widget class="QPushButton" name="readFreq">
+             <property name="enabled">
+              <bool>false</bool>
+             </property>
+             <property name="toolTip">
+              <string>&lt;html&gt;&lt;head/&gt;&lt;body&gt;&lt;p&gt;If orange or red there has been a rig control failure, click to reset and read the dial frequency.  S implies split mode.&lt;/p&gt;&lt;/body&gt;&lt;/html&gt;</string>
+             </property>
+             <property name="accessibleDescription">
+              <string>If orange or red there has been a rig control failure, click to reset and read the dial frequency. S implies split mode.</string>
+             </property>
+             <property name="styleSheet">
+              <string notr="true">QPushButton {
+ font-family: helvetica;
+ font-size: 9pt;
+ font-weight: bold;
+ background-color: white;
+ color: black;
+ border-style: solid;
+ border-width:1px;
+ border-radius:10px;
+ border-color: gray;
+ max-width:20px;
+ max-height:20px;
+ min-width:20px;
+ min-height:20px;
+}
+QPushButton[state=&quot;error&quot;] {
+ background-color: red;
+}
+QPushButton[state=&quot;warning&quot;] {
+ background-color: orange;
+}
+QPushButton[state=&quot;ok&quot;] {
+ background-color: #00ff00;
+}</string>
+             </property>
+             <property name="text">
+              <string>?</string>
+             </property>
+            </widget>
+           </item>
+          </layout>
+         </item>
         </layout>
        </item>
       </layout>
@@ -3014,8 +3076,8 @@ QLabel[oob=&quot;true&quot;] {
     <rect>
      <x>0</x>
      <y>0</y>
-     <width>893</width>
-     <height>21</height>
+     <width>901</width>
+     <height>22</height>
     </rect>
    </property>
    <widget class="QMenu" name="menuFile">
@@ -3026,8 +3088,6 @@ QLabel[oob=&quot;true&quot;] {
     <addaction name="actionOpen_next_in_directory"/>
     <addaction name="actionDecode_remaining_files_in_directory"/>
     <addaction name="separator"/>
-    <addaction name="actionCopy_to_WSJTX_txt"/>
-    <addaction name="separator"/>
     <addaction name="actionDelete_all_wav_files_in_SaveDir"/>
     <addaction name="actionErase_ALL_TXT"/>
     <addaction name="actionErase_wsjtx_log_adi"/>
@@ -3038,6 +3098,7 @@ QLabel[oob=&quot;true&quot;] {
     <addaction name="separator"/>
     <addaction name="actionSettings"/>
     <addaction name="separator"/>
+    <addaction name="separator"/>
     <addaction name="actionExit"/>
    </widget>
    <widget class="QMenu" name="menuView">
@@ -3670,11 +3731,6 @@ QLabel[oob=&quot;true&quot;] {
     <string>Active Stations</string>
    </property>
   </action>
-  <action name="actionCopy_to_WSJTX_txt">
-   <property name="text">
-    <string>Copy main text window to WSJT-X.txt</string>
-   </property>
-  </action>
  </widget>
  <layoutdefault spacing="6" margin="11"/>
  <customwidgets>
@@ -3734,7 +3790,6 @@ QLabel[oob=&quot;true&quot;] {
   <tabstop>stopTxButton</tabstop>
   <tabstop>tuneButton</tabstop>
   <tabstop>cbMenus</tabstop>
-  <tabstop>bandComboBox</tabstop>
   <tabstop>sbNB</tabstop>
   <tabstop>dxCallEntry</tabstop>
   <tabstop>dxGridEntry</tabstop>
diff --git a/widgets/plotter.cpp b/widgets/plotter.cpp
index afa512ff2..189f42d40 100644
--- a/widgets/plotter.cpp
+++ b/widgets/plotter.cpp
@@ -100,7 +100,6 @@ void CPlotter::resizeEvent(QResizeEvent* )                    //resizeEvent()
     if(m_bReference) m_h2=m_h-30;
     if(m_h2<1) m_h2=1;
     m_h1=m_h-m_h2;
-//    m_line=0;
     m_2DPixmap = QPixmap(m_Size.width(), m_h2);
     m_2DPixmap.fill(Qt::black);
     m_WaterfallPixmap = QPixmap(m_Size.width(), m_h1);
@@ -112,6 +111,8 @@ void CPlotter::resizeEvent(QResizeEvent* )                    //resizeEvent()
     m_ScalePixmap.fill(Qt::white);
     m_Percent2DScreen0 = m_Percent2DScreen;
     m_bResized = true;
+    m_vpixperdiv = float(m_h2)/float(VERT_DIVS);
+    m_x=0;
   }
   DrawOverlay();
 }
@@ -167,6 +168,8 @@ void CPlotter::draw(float swide[], bool bScroll, bool bRed)
   static QPoint LineBuf[MAX_SCREENSIZE];
   static QPoint LineBuf2[MAX_SCREENSIZE];
   static QPoint LineBuf3[MAX_SCREENSIZE];
+  static QPoint LineBuf4[MAX_SCREENSIZE];
+
   j=0;
   j0=int(m_startFreq/m_fftBinWidth + 0.5);
   int iz=XfromFreq(5000.0);
@@ -231,7 +234,7 @@ void CPlotter::draw(float swide[], bool bScroll, bool bRed)
 
     }
 
-    if(i==iz-1 and !m_bQ65_Sync) {
+    if(i==iz-1 and !m_bQ65_Sync and !m_bTotalPower) {
       painter2D.drawPolyline(LineBuf,j);
     }
     LineBuf[j].setX(i);
@@ -320,6 +323,22 @@ void CPlotter::draw(float swide[], bool bScroll, bool bRed)
       painter2D.drawText(m_w-100,m_h2/2,t);
     }
   }
+
+  if(m_bTotalPower and m_pdB>1.0) {
+    painter2D.setPen(Qt::green);
+    if(m_x==m_w-1) {
+      for (int i=0; i<m_w-1; i++) {
+        LineBuf4[i].setY(LineBuf4[i+1].y());
+      }
+    }
+    int yy=m_h2 - 0.1*m_vpixperdiv*(m_pdB-20.0);
+    LineBuf4[m_x].setX(m_x);
+    LineBuf4[m_x].setY(yy);
+    if(LineBuf4[m_w-1].y()==0) LineBuf4[m_w-1].setY(yy);
+    painter2D.drawPolyline(LineBuf4,m_x);
+    if(m_x < m_w-1) m_x++;
+  }
+
   update();                                    //trigger a new paintEvent
   m_bScaleOK=true;
 }
@@ -333,6 +352,7 @@ void CPlotter::drawRed(int ia, int ib, float swide[])
 
 void CPlotter::replot()
 {
+  resizeEvent(NULL);
   float swide[m_w];
   m_bReplot=true;
   for(int irow=0; irow<m_h1; irow++) {
@@ -369,7 +389,6 @@ void CPlotter::DrawOverlay()                   //DrawOverlay()
   painter.setBrush(Qt::SolidPattern);
 
   m_fSpan = w*df;
-//  int n=m_fSpan/10;
   m_freqPerDiv=10;
   if(m_fSpan>100) m_freqPerDiv=20;
   if(m_fSpan>250) m_freqPerDiv=50;
@@ -377,25 +396,48 @@ void CPlotter::DrawOverlay()                   //DrawOverlay()
   if(m_fSpan>1000) m_freqPerDiv=200;
   if(m_fSpan>2500) m_freqPerDiv=500;
 
-  pixperdiv = m_freqPerDiv/df;
-  m_hdivs = w*df/m_freqPerDiv + 1.9999;
-
-  float xx0=float(m_startFreq)/float(m_freqPerDiv);
-  xx0=xx0-int(xx0);
-  int x0=xx0*pixperdiv+0.5;
-  for( int i=1; i<m_hdivs; i++) {                  //draw vertical grids
-    x = (int)((float)i*pixperdiv ) - x0;
-    if(x >= 0 and x<=m_w) {
-      painter.setPen(QPen(Qt::white, 1,Qt::DotLine));
-      painter.drawLine(x, 0, x , m_h2);
+  if(!m_bTotalPower) {
+    pixperdiv = m_freqPerDiv/df;
+    m_hdivs = w*df/m_freqPerDiv + 1.9999;
+    float xx0=float(m_startFreq)/float(m_freqPerDiv);
+    xx0=xx0-int(xx0);
+    int x0=xx0*pixperdiv+0.5;
+    for( int i=1; i<m_hdivs; i++) {                 //draw vertical grids
+      x = (int)((float)i*pixperdiv ) - x0;
+      if(x >= 0 and x<=m_w) {
+        painter.setPen(QPen(Qt::white, 1,Qt::DotLine));
+        painter.drawLine(x, 0, x , m_h2);
+      }
     }
   }
 
-  pixperdiv = (float)m_h2 / (float)VERT_DIVS;
   painter.setPen(QPen(Qt::white, 1,Qt::DotLine));
-  for( int i=1; i<VERT_DIVS; i++) {                //draw horizontal grids
-    y = (int)( (float)i*pixperdiv );
-    painter.drawLine(0, y, w, y);
+  if(m_bTotalPower) painter.setPen(QPen(Qt::white, 1,Qt::DashLine));
+  for( int i=1; i<VERT_DIVS; i++) {                 //draw horizontal grids
+    y = int(i*m_vpixperdiv);
+    if(m_bTotalPower) {
+        painter.drawLine(15, y, w, y);
+    } else {
+        painter.drawLine(0, y, w, y);
+    }
+  }
+
+  if(m_bTotalPower) {
+    painter.setPen(QPen(Qt::white));
+    for( int i=1; i<VERT_DIVS; i++) {               //draw horizontal grids
+      y = int(i*m_vpixperdiv);
+      painter.drawText(0,y+5,QString::number(10*(VERT_DIVS-i) + 20));
+    }
+  }
+
+  if(m_bTotalPower and m_h2>100) {
+    painter.setPen(QPen(Qt::white, 1,Qt::DotLine));
+    for( int i=1; i<5*VERT_DIVS; i++) {             //draw horizontal 2 dB grids
+      if(i%5 > 0) {
+        y = int(0.2*i*m_vpixperdiv);
+        painter.drawLine(0, y, w, y);
+      }
+    }
   }
 
   QRect rect0;
@@ -730,7 +772,15 @@ int CPlotter::rxFreq() {return m_rxFreq;}                      //rxFreq
 void CPlotter::mouseMoveEvent (QMouseEvent * event)
 {
   int x=event->x();
-  QToolTip::showText(event->globalPos(),QString::number(int(FreqfromX(x))));
+  int y=event->y();
+  float pdB=10.0*(m_h-y)/m_vpixperdiv + 20.0;
+  if(y<(m_h-m_h2)) {
+    QToolTip::showText(event->globalPos(),QString::number(int(FreqfromX(x))));
+  } else {
+    QString t;
+    t=t.asprintf("%4.1f dB",pdB);
+    QToolTip::showText(event->globalPos(),t);
+  }
   QWidget::mouseMoveEvent(event);
 }
 
@@ -874,3 +924,13 @@ void CPlotter::setDiskUTC(int nutc)
 {
   m_nUTC=nutc;
 }
+
+void CPlotter::drawTotalPower(float pdB)
+{
+  m_pdB=pdB;
+}
+
+void CPlotter::restartTotalPower()
+{
+  m_x=0;
+}
diff --git a/widgets/plotter.h b/widgets/plotter.h
index d1aa064aa..d01c98102 100644
--- a/widgets/plotter.h
+++ b/widgets/plotter.h
@@ -34,6 +34,7 @@ public:
   QSize sizeHint() const Q_DECL_OVERRIDE;
 
   void draw(float swide[], bool bScroll, bool bRed);		//Update the waterfall
+  void drawTotalPower(float pdB);
   void replot();
   void SetRunningState(bool running);
   void setPlotZero(int plotZero);
@@ -81,12 +82,15 @@ public:
   bool Reference() const {return m_bReference;}
   void setQ65_Sync(bool b) {m_bQ65_Sync = b;}
   bool Q65_Sync() const {return m_bQ65_Sync;}
+  void setTotalPower(bool b) {m_bTotalPower = b;}
+  bool TotalPower() const {return m_bTotalPower;}
   void drawRed(int ia, int ib, float swide[]);
   void setVHF(bool bVHF);
   void setRedFile(QString fRed);
   void setFST4_FreqRange(int fLow,int fHigh);
   void setSingleDecode(bool b);
   void setDiskUTC(int nutc);
+  void restartTotalPower();
 
   bool scaleOK () const {return m_bScaleOK;}
 signals:
@@ -116,12 +120,15 @@ private:
   bool    m_bReference;
   bool    m_bReference0;
   bool    m_bQ65_Sync;
+  bool    m_bTotalPower;
   bool    m_bVHF;
   bool    m_bSingleDecode;
   bool    m_bFirst=true;
   bool    m_bResized;
 
   float   m_fSpan;
+  float   m_pdB=0.0;
+  float   m_vpixperdiv;
 
   qint32  m_plotZero;
   qint32  m_plotGain;
@@ -137,6 +144,7 @@ private:
   qint32  m_nfa;
   qint32  m_nfb;
   qint32  m_nUTC;
+  qint32  m_x=0;
 
   QPixmap m_WaterfallPixmap;
   QPixmap m_2DPixmap;
diff --git a/widgets/widegraph.cpp b/widgets/widegraph.cpp
index e1ad518ab..7119eda35 100644
--- a/widgets/widegraph.cpp
+++ b/widgets/widegraph.cpp
@@ -71,11 +71,13 @@ WideGraph::WideGraph(QSettings * settings, QWidget *parent) :
     ui->widePlot->setLinearAvg(m_settings->value("LinearAvg",false).toBool());
     ui->widePlot->setReference(m_settings->value("Reference",false).toBool());
     ui->widePlot->setQ65_Sync(m_settings->value("Q65_Sync",false).toBool());
+    ui->widePlot->setTotalPower(m_settings->value("TotalPower",false).toBool());
     if(ui->widePlot->current()) ui->spec2dComboBox->setCurrentIndex(0);
     if(ui->widePlot->cumulative()) ui->spec2dComboBox->setCurrentIndex(1);
     if(ui->widePlot->linearAvg()) ui->spec2dComboBox->setCurrentIndex(2);
     if(ui->widePlot->Reference()) ui->spec2dComboBox->setCurrentIndex(3);
     if(ui->widePlot->Q65_Sync()) ui->spec2dComboBox->setCurrentIndex(4);
+    if(ui->widePlot->TotalPower()) ui->spec2dComboBox->setCurrentIndex(5);
     int nbpp=m_settings->value("BinsPerPixel",2).toInt();
     ui->widePlot->setBinsPerPixel(nbpp);
     ui->sbPercent2dPlot->setValue(m_Percent2DScreen);
@@ -133,6 +135,7 @@ void WideGraph::saveSettings()                                           //saveS
   m_settings->setValue ("LinearAvg", ui->widePlot->linearAvg());
   m_settings->setValue ("Reference", ui->widePlot->Reference());
   m_settings->setValue ("Q65_Sync", ui->widePlot->Q65_Sync());
+  m_settings->setValue ("TotalPower", ui->widePlot->TotalPower());
   m_settings->setValue ("BinsPerPixel", ui->widePlot->binsPerPixel ());
   m_settings->setValue ("StartFreq", ui->widePlot->startFreq ());
   m_settings->setValue ("WaterfallPalette", m_waterfallPalette);
@@ -148,11 +151,12 @@ void WideGraph::drawRed(int ia, int ib)
   ui->widePlot->drawRed(ia,ib,m_swide);
 }
 
-void WideGraph::dataSink2(float s[], float df3, int ihsym, int ndiskdata)  //dataSink2
+void WideGraph::dataSink2(float s[], float df3, int ihsym, int ndiskdata, float pdB)  //dataSink2
 {
   static float splot[NSMAX];
   int nbpp = ui->widePlot->binsPerPixel();
 
+  if(ui->widePlot->TotalPower()) ui->widePlot->drawTotalPower(pdB);
 //Average spectra over specified number, m_waterfallAvg
   if (m_n==0) {
     for (int i=0; i<NSMAX; i++)
@@ -313,6 +317,7 @@ void WideGraph::on_spec2dComboBox_currentIndexChanged(int index)
   ui->widePlot->setLinearAvg(false);
   ui->widePlot->setReference(false);
   ui->widePlot->setQ65_Sync(false);
+  ui->widePlot->setTotalPower(false);
   ui->smoSpinBox->setEnabled(false);
   switch (index)
     {
@@ -332,7 +337,10 @@ void WideGraph::on_spec2dComboBox_currentIndexChanged(int index)
     case 4:
       ui->widePlot->setQ65_Sync(true);
       break;
-  }
+    case 5:
+      ui->widePlot->setTotalPower(true);
+      break;
+    }
   replot();
 }
 
@@ -473,6 +481,7 @@ void WideGraph::on_zeroSlider_valueChanged(int value)                 //Zero
 void WideGraph::on_gain2dSlider_valueChanged(int value)               //Gain2
 {
   ui->widePlot->setPlot2dGain(value);
+  if(ui->widePlot->TotalPower()) return;
   if(ui->widePlot->scaleOK ()) {
     ui->widePlot->draw(m_swide,false,false);
     if(m_mode=="Q65") ui->widePlot->draw(m_swide,false,true);
@@ -482,6 +491,7 @@ void WideGraph::on_gain2dSlider_valueChanged(int value)               //Gain2
 void WideGraph::on_zero2dSlider_valueChanged(int value)               //Zero2
 {
   ui->widePlot->setPlot2dZero(value);
+  if(ui->widePlot->TotalPower()) return;
   if(ui->widePlot->scaleOK ()) {
     ui->widePlot->draw(m_swide,false,false);
     if(m_mode=="Q65") ui->widePlot->draw(m_swide,false,true);
@@ -540,3 +550,8 @@ void WideGraph::setDiskUTC(int nutc)
 {
   ui->widePlot->setDiskUTC(nutc);
 }
+
+void WideGraph::restartTotalPower()
+{
+  ui->widePlot->restartTotalPower();
+}
diff --git a/widgets/widegraph.h b/widgets/widegraph.h
index 9043f691f..795031a46 100644
--- a/widgets/widegraph.h
+++ b/widgets/widegraph.h
@@ -26,7 +26,7 @@ public:
   explicit WideGraph(QSettings *, QWidget *parent = 0);
   ~WideGraph ();
 
-  void   dataSink2(float s[], float df3, int ihsym, int ndiskdata);
+  void   dataSink2(float s[], float df3, int ihsym, int ndiskdata, float pdB);
   void   setRxFreq(int n);
   int    rxFreq();
   int    nStartFreq();
@@ -51,6 +51,7 @@ public:
   void   setFST4_FreqRange(int fLow,int fHigh);
   void   setSingleDecode(bool b);
   void   setDiskUTC(int nutc);
+  void   restartTotalPower();
 
 signals:
   void freezeDecode2(int n);
diff --git a/widgets/widegraph.ui b/widgets/widegraph.ui
index 758cad8c4..7259dd8c7 100644
--- a/widgets/widegraph.ui
+++ b/widgets/widegraph.ui
@@ -340,6 +340,11 @@
           <string>Q65_Sync</string>
          </property>
         </item>
+        <item>
+         <property name="text">
+          <string>Total power (dB)</string>
+         </property>
+        </item>
        </widget>
       </item>
       <item row="0" column="2">