diff --git a/libm65/afc65b.f90 b/libm65/afc65b.f90
index eb7e74d51..4e3acf3fa 100644
--- a/libm65/afc65b.f90
+++ b/libm65/afc65b.f90
@@ -1,4 +1,4 @@
-subroutine afc65b(cx,cy,npts,nfast,fsample,nflip,ipol,xpol,ndphi,iloop,  &
+subroutine afc65b(cx,cy,npts,fsample,nflip,ipol,xpol,ndphi,iloop,  &
      a,ccfbest,dtbest)
 
   logical xpol
@@ -26,11 +26,11 @@ subroutine afc65b(cx,cy,npts,nfast,fsample,nflip,ipol,xpol,ndphi,iloop,  &
   chisqr0=1.e6
   do iter=1,3                               !One iteration is enough?
      do j=1,nterms
-        chisq1=fchisq(cx,cy,npts,nfast,fsample,nflip,a,ccfmax,dtmax)
+        chisq1=fchisq(cx,cy,npts,fsample,nflip,a,ccfmax,dtmax)
         fn=0.
         delta=deltaa(j)
 10      a(j)=a(j)+delta
-        chisq2=fchisq(cx,cy,npts,nfast,fsample,nflip,a,ccfmax,dtmax)
+        chisq2=fchisq(cx,cy,npts,fsample,nflip,a,ccfmax,dtmax)
         if(chisq2.eq.chisq1) go to 10
         if(chisq2.gt.chisq1) then
            delta=-delta                      !Reverse direction
@@ -41,7 +41,7 @@ subroutine afc65b(cx,cy,npts,nfast,fsample,nflip,ipol,xpol,ndphi,iloop,  &
         endif
 20      fn=fn+1.0
         a(j)=a(j)+delta
-        chisq3=fchisq(cx,cy,npts,nfast,fsample,nflip,a,ccfmax,dtmax)
+        chisq3=fchisq(cx,cy,npts,fsample,nflip,a,ccfmax,dtmax)
         if(chisq3.lt.chisq2) then
            chisq1=chisq2
            chisq2=chisq3
@@ -53,7 +53,7 @@ subroutine afc65b(cx,cy,npts,nfast,fsample,nflip,ipol,xpol,ndphi,iloop,  &
         a(j)=a(j)-delta
         deltaa(j)=deltaa(j)*fn/3.
      enddo
-     chisqr=fchisq(cx,cy,npts,nfast,fsample,nflip,a,ccfmax,dtmax)
+     chisqr=fchisq(cx,cy,npts,fsample,nflip,a,ccfmax,dtmax)
      if(chisqr/chisqr0.gt.0.9999) go to 30
      chisqr0=chisqr
   enddo
diff --git a/libm65/ccf65.f90 b/libm65/ccf65.f90
index 94858a645..1bebb8d73 100644
--- a/libm65/ccf65.f90
+++ b/libm65/ccf65.f90
@@ -1,4 +1,4 @@
-subroutine ccf65(ss,nhsym,nfast,ssmax,sync1,ipol1,jpz,dt1,flipk,      &
+subroutine ccf65(ss,nhsym,ssmax,sync1,ipol1,jpz,dt1,flipk,      &
      syncshort,snr2,ipol2,dt2)
 
   parameter (NFFT=512,NH=NFFT/2)
@@ -15,7 +15,7 @@ subroutine ccf65(ss,nhsym,nfast,ssmax,sync1,ipol1,jpz,dt1,flipk,      &
   real ccf(-11:54,4)
   logical first
   integer npr(126)
-  data first/.true./,nfast0/-99/
+  data first/.true./
   equivalence (s,cs),(pr,cpr),(s2,cs2),(pr2,cpr2)
   save
 
@@ -29,14 +29,13 @@ subroutine ccf65(ss,nhsym,nfast,ssmax,sync1,ipol1,jpz,dt1,flipk,      &
       0,1,0,1,0,0,1,1,0,0,1,0,0,1,0,0,0,0,1,1,     &
       1,1,1,1,1,1/
 
-  if(first .or. nfast.ne.nfast0) then
+  if(first) then
 ! Initialize pr, pr2; compute cpr, cpr2.
      fac=1.0/NFFT
      do i=1,NFFT
         pr(i)=0.
         pr2(i)=0.
         k=2*mod((i-1)/8,2)-1
-        if(nfast.eq.2) k=2*mod((i-1)/16,2)-1
         if(i.le.NH) pr2(i)=fac*k
      enddo
      do i=1,126
@@ -48,7 +47,6 @@ subroutine ccf65(ss,nhsym,nfast,ssmax,sync1,ipol1,jpz,dt1,flipk,      &
      call four2a(pr,NFFT,1,-1,0)
      call four2a(pr2,NFFT,1,-1,0)
      first=.false.
-     nfast0=nfast
   endif
 
 ! Look for JT65 sync pattern and shorthand square-wave pattern.
@@ -108,7 +106,7 @@ subroutine ccf65(ss,nhsym,nfast,ssmax,sync1,ipol1,jpz,dt1,flipk,      &
   enddo
   rms=sqrt(sq/49.0)
   sync1=ccfbest/rms - 4.0
-  dt1=lagpk*(2048.0/11025.0)/nfast - 2.5
+  dt1=lagpk*(2048.0/11025.0) - 2.5
 
 ! Find base level for normalizing snr2.
   do i=1,nhsym
@@ -117,7 +115,7 @@ subroutine ccf65(ss,nhsym,nfast,ssmax,sync1,ipol1,jpz,dt1,flipk,      &
   call pctile(tmp1,nhsym,40,base)
   snr2=0.398107*ccfbest2/base                !### empirical
   syncshort=0.5*ccfbest2/rms - 4.0           !### better normalizer than rms?
-  dt2=(2.5 + lagpk2*(2048.0/11025.0))/nfast
+  dt2=2.5 + lagpk2*(2048.0/11025.0)
 
   return
 end subroutine ccf65
diff --git a/libm65/cgen65.f90 b/libm65/cgen65.f90
index 655de97ac..2f653ffa9 100644
--- a/libm65/cgen65.f90
+++ b/libm65/cgen65.f90
@@ -1,4 +1,4 @@
-subroutine cgen65(message,mode65,nfast,samfac,nsendingsh,msgsent,cwave,nwave)
+subroutine cgen65(message,mode65,samfac,nsendingsh,msgsent,cwave,nwave)
 
 ! Encodes a JT65 message into a wavefile.  
 ! Executes in 17 ms on opti-745.
@@ -43,10 +43,10 @@ subroutine cgen65(message,mode65,nfast,samfac,nsendingsh,msgsent,cwave,nwave)
      call interleave63(sent,1)           !Apply interleaving
      call graycode(sent,63,1)            !Apply Gray code
      nsym=126                            !Symbols per transmission
-     tsymbol=4096.d0/(nfast*11025.d0)    !Time per symbol
+     tsymbol=4096.d0/11025.d0            !Time per symbol
   else
      nsendingsh=1                        !Flag for shorthand message
-     nsym=32/nfast
+     nsym=32
      tsymbol=16384.d0/11025.d0
   endif
 
diff --git a/libm65/decode0.f90 b/libm65/decode0.f90
index 01df138de..acc5bc228 100644
--- a/libm65/decode0.f90
+++ b/libm65/decode0.f90
@@ -54,7 +54,7 @@ subroutine decode0(dd,ss,savg,nstandalone)
   call map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,           &
        mousedf,mousefqso,nagain,ndecdone,ndiskdat,nfshift,ndphi,           &
        nfcal,nkeep,mcall3b,nsum,nsave,nxant,rmsdd,mycall,mygrid,          &
-       neme,ndepth,hiscall,hisgrid,nhsym,nfsample,nxpol,nmode,nfast)
+       neme,ndepth,hiscall,hisgrid,nhsym,nfsample,nxpol,nmode)
 
   call timer('map65a  ',1)
   call timer('decode0 ',1)
diff --git a/libm65/decode1a.f90 b/libm65/decode1a.f90
index 3adcaec7b..bec03e7a8 100644
--- a/libm65/decode1a.f90
+++ b/libm65/decode1a.f90
@@ -1,4 +1,4 @@
-subroutine decode1a(dd,newdat,f0,nflip,mode65,nfast,nfsample,xpol,          &
+subroutine decode1a(dd,newdat,f0,nflip,mode65,nfsample,xpol,          &
      mycall,hiscall,hisgrid,neme,ndepth,nqd,dphi,ndphi,iloop,               &
      nutc,nkhz,ndf,ipol,ntol,bqra64,sync2,a,dt,pol,nkv,nhist,nsum,nsave,    &
      qual,decoded)
@@ -24,7 +24,7 @@ subroutine decode1a(dd,newdat,f0,nflip,mode65,nfast,nfsample,xpol,          &
 ! Mix sync tone to baseband, low-pass filter, downsample to 1378.125 Hz
   dt00=dt
   call timer('filbig  ',0)
-  call filbig(dd,NMAX,nfast,f0,newdat,nfsample,xpol,cx,cy,n5)
+  call filbig(dd,NMAX,f0,newdat,nfsample,xpol,cx,cy,n5)
 ! NB: cx, cy have sample rate 96000*77125/5376000 = 1378.125 Hz
   call timer('filbig  ',1)
   if(nqd.eq.2) goto 900
@@ -68,7 +68,7 @@ subroutine decode1a(dd,newdat,f0,nflip,mode65,nfast,nfsample,xpol,          &
 ! factor of 1/8, say?  Should be a significant execution speed-up.
   call timer('afc65b  ',0)
 ! Best fit for DF, f1, f2, pol
-  call afc65b(c5x(i0),c5y(i0),nz,nfast,fsample,nflip,ipol,xpol,      &
+  call afc65b(c5x(i0),c5y(i0),nz,fsample,nflip,ipol,xpol,      &
        ndphi,iloop,a,ccfbest,dtbest)
   call timer('afc65b  ',1)
 
@@ -92,9 +92,8 @@ subroutine decode1a(dd,newdat,f0,nflip,mode65,nfast,nfsample,xpol,          &
 ! submodes B and C).
 
   nsym=126
-  nfft=512/nfast
+  nfft=512
   j=(dt00+dtbest+2.685)*1378.125
-  if(nfast.eq.2) j=j-1506
   if(j.lt.0) j=0
 
   call timer('sh_ffts ',0)
@@ -114,9 +113,8 @@ subroutine decode1a(dd,newdat,f0,nflip,mode65,nfast,nfsample,xpol,          &
            do i=1,66
 !                  s2(i,k)=real(c5a(i))**2 + aimag(c5a(i))**2
               jj=i
-              if(nfast.eq.1 .and. mode65.eq.2) jj=2*i-1
-              if(nfast.eq.2 .and. mode65.eq.4) jj=2*i-1
-              if(nfast.eq.1 .and. mode65.eq.4) jj=4*i-3
+              if(mode65.eq.2) jj=2*i-1
+              if(mode65.eq.4) jj=4*i-3
               s2(i,k)=real(c5a(jj))**2 + aimag(c5a(jj))**2
            enddo
         else
@@ -134,7 +132,6 @@ subroutine decode1a(dd,newdat,f0,nflip,mode65,nfast,nfsample,xpol,          &
   call decode65b(s2,flip,mycall,hiscall,hisgrid,mode65,neme,ndepth,    &
        nqd,nkv,nhist,qual,decoded,s3,sy)
   dt=dt00 + dtbest + 1.7
-  if(nfast.eq.2) dt=dt00 + dtbest + 0.6
   call timer('dec65b  ',1)
 
   if(nqd.eq.1 .and. decoded.eq.'                      ') then
diff --git a/libm65/fchisq.f90 b/libm65/fchisq.f90
index ced1a92e7..b0005346d 100644
--- a/libm65/fchisq.f90
+++ b/libm65/fchisq.f90
@@ -1,4 +1,4 @@
-real function fchisq(cx,cy,npts,nfast,fsample,nflip,a,ccfmax,dtmax)
+real function fchisq(cx,cy,npts,fsample,nflip,a,ccfmax,dtmax)
 
   parameter (NMAX=60*96000)          !Samples per 60 s
   complex cx(npts),cy(npts)
@@ -10,7 +10,7 @@ real function fchisq(cx,cy,npts,nfast,fsample,nflip,a,ccfmax,dtmax)
   save
 
   call timer('fchisq  ',0)
-  baud=nfast*11025.0/4096.0
+  baud=11025.0/4096.0
   nsps=nint(fsample/baud)                  !Samples per symbol
   nsph=nsps/2                              !Samples per half-symbol
   ndiv=16                                  !Output ss() steps per symbol
diff --git a/libm65/filbig.f90 b/libm65/filbig.f90
index 12b3299d3..92a489237 100644
--- a/libm65/filbig.f90
+++ b/libm65/filbig.f90
@@ -1,4 +1,4 @@
-subroutine filbig(dd,nmax,nfast,f0,newdat,nfsample,xpol,c4a,c4b,n4)
+subroutine filbig(dd,nmax,f0,newdat,nfsample,xpol,c4a,c4b,n4)
 
 ! Filter and downsample complex data stored in array dd(4,nmax).  
 ! Output is downsampled from 96000 Hz to 1375.125 Hz.
@@ -16,40 +16,21 @@ subroutine filbig(dd,nmax,nfast,f0,newdat,nfsample,xpol,c4a,c4b,n4)
   include 'fftw3.f'
   common/cacb/ca,cb
   equivalence (rfilt,cfilt)
-  data first/.true./,npatience/1/,nfast0/0/
+  data first/.true./,npatience/1/
   data halfpulse/114.97547150,36.57879257,-20.93789101,                &
        5.89886379,1.59355187,-2.49138308,0.60910773,-0.04248129/
   save
 
   if(nmax.lt.0) go to 900
 
-  if(nfast.eq.1) then
-     nfft1=MAXFFT1
-     nfft2=MAXFFT2
-     if(nfsample.eq.95238) then
-        nfft1=5120000
-        nfft2=74088
-     endif
-  else
-     nfft1=2621440
-     nfft2=37632
-     if(nfsample.eq.95238) then
-        nfft1=2560000
-        nfft2=37044
-     endif
+  nfft1=MAXFFT1
+  nfft2=MAXFFT2
+  if(nfsample.eq.95238) then
+     nfft1=5120000
+     nfft2=74088
   endif
 
-  if(nfast.ne.nfast0) then
-     if(nfast0.ne.0) then
-        call sfftw_destroy_plan(plan1)
-        call sfftw_destroy_plan(plan2)
-        call sfftw_destroy_plan(plan3)
-        call sfftw_destroy_plan(plan4)
-        call sfftw_destroy_plan(plan5)
-     endif
-  endif
-
-  if(first .or. nfast.ne.nfast0) then
+  if(first) then
      nflags=FFTW_ESTIMATE
      if(npatience.eq.1) nflags=FFTW_ESTIMATE_PATIENT
      if(npatience.eq.2) nflags=FFTW_MEASURE
@@ -88,7 +69,6 @@ subroutine filbig(dd,nmax,nfast,f0,newdat,nfsample,xpol,c4a,c4b,n4)
      if(nfsample.eq.95238) df=95238.1d0/nfft1
      first=.false.
   endif
-  nfast0=nfast
 
 ! When new data comes along, we need to compute a new "big FFT"
 ! If we just have a new f0, continue with the existing ca and cb.
diff --git a/libm65/gen65.f90 b/libm65/gen65.f90
index 0d212d68d..f09d0868a 100644
--- a/libm65/gen65.f90
+++ b/libm65/gen65.f90
@@ -1,4 +1,4 @@
-subroutine gen65(message,mode65,nfast,samfac,nsendingsh,msgsent,iwave,nwave)
+subroutine gen65(message,mode65,samfac,nsendingsh,msgsent,iwave,nwave)
 
 ! Encodes a JT65 message into a wavefile.  
 ! Executes in 17 ms on opti-745.
@@ -43,9 +43,9 @@ subroutine gen65(message,mode65,nfast,samfac,nsendingsh,msgsent,iwave,nwave)
      call interleave63(sent,1)           !Apply interleaving
      call graycode(sent,63,1)            !Apply Gray code
      nsym=126                            !Symbols per transmission
-     nsps=4096/nfast
+     nsps=4096
   else
-     nsym=32/nfast
+     nsym=32
      nsps=16384
      nsendingsh=1                         !Flag for shorthand message
   endif
diff --git a/libm65/m65.f90 b/libm65/m65.f90
index 11a821934..6d1721b66 100644
--- a/libm65/m65.f90
+++ b/libm65/m65.f90
@@ -39,8 +39,6 @@ program m65
   if(arg(1:1).eq.'B') nmode=2
   if(arg(1:1).eq.'C') nmode=3
 !###
-  nfast=1
-  if(arg(2:2).eq.'2') nfast=2
   nfsample=96000
   call getarg(2,arg)
   if(arg.eq.'95238') then
@@ -108,7 +106,7 @@ program m65
            gainy=1.0265
            phasex=0.01426
            phasey=-0.01195
-           call symspec(k,nfast,nxpol,ndiskdat,nb,nbslider,idphi,nfsample,   &
+           call symspec(k,nxpol,ndiskdat,nb,nbslider,idphi,nfsample,   &
                 fgreen,iqadjust,iqapply,gainx,gainy,phasex,phasey,rejectx,   &
                 rejecty,pxdb,pydb,ssz5a,nkhz,ihsym,nzap,slimit,lstrong)
            call timer('symspec ',1)
diff --git a/libm65/map65a.f90 b/libm65/map65a.f90
index 00a6a8213..caaa25dc8 100644
--- a/libm65/map65a.f90
+++ b/libm65/map65a.f90
@@ -1,7 +1,7 @@
 subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
      mousedf,mousefqso,nagain,ndecdone,ndiskdat,nfshift,ndphi,              &
      nfcal,nkeep,mcall3b,nsum,nsave,nxant,rmsdd,mycall,mygrid,              &
-     neme,ndepth,hiscall,hisgrid,nhsym,nfsample,nxpol,nmode,nfast)
+     neme,ndepth,hiscall,hisgrid,nhsym,nfsample,nxpol,nmode)
 
 !  Processes timf2 data from Linrad to find and decode JT65 signals.
 
@@ -123,7 +123,7 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
 !  Look for JT65 sync patterns and shorthand square-wave patterns.
               call timer('ccf65   ',0)
               ssmax=smax
-              call ccf65(ss(1,1,i),nhsym,nfast,ssmax,sync1,ipol,jpz,dt,     &
+              call ccf65(ss(1,1,i),nhsym,ssmax,sync1,ipol,jpz,dt,     &
                    flipk,syncshort,snr2,ipol2,dt2)
               call timer('ccf65   ',1)
 
@@ -217,7 +217,7 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
                  ifreq=i
                  ikHz=nint(freq+0.5*(nfa+nfb)-foffset)-nfshift
                  idf=nint(1000.0*(freq+0.5*(nfa+nfb)-foffset-(ikHz+nfshift)))
-                 call decode1a(dd,newdat,f00,nflip,mode65,nfast,nfsample, &
+                 call decode1a(dd,newdat,f00,nflip,mode65,nfsample, &
                       xpol,mycall,hiscall,hisgrid,neme,ndepth,nqd,dphi,   &
                       ndphi,iloop,nutc,ikHz,idf,ipol,ntol,bqra64,sync2,   &
                       a,dt,pol,nkv,nhist,nsum,nsave,qual,decoded)
@@ -288,11 +288,9 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
 
               s2db=10.0*log10(sync2) - 40             !### empirical ###
               nsync2=nint(s2db)
-              if(nfast.eq.2) nsync2=nint(s2db + 6.5)
               if(decoded(1:4).eq.'RO  ' .or. decoded(1:4).eq.'RRR  ' .or.  &
                    decoded(1:4).eq.'73  ') then
-                 if(nfast.eq.1) nsync2=nint(1.33*s2db + 2.0)
-                 if(nfast.eq.2) nsync2=nint(1.33*s2db + 2.7)
+                 nsync2=nint(1.33*s2db + 2.0)
               endif
 
               nwrite=nwrite+1
@@ -418,11 +416,9 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
 
            s2db=10.0*log10(sync2) - 40             !### empirical ###
            nsync2=nint(s2db)
-           if(nfast.eq.2) nsync2=nint(s2db + 6.5)
            if(decoded(1:4).eq.'RO  ' .or. decoded(1:4).eq.'RRR  ' .or.  &
                 decoded(1:4).eq.'73  ') then
-              if(nfast.eq.1) nsync2=nint(1.33*s2db + 2.0)
-              if(nfast.eq.2) nsync2=nint(1.33*s2db + 2.7)
+              nsync2=nint(1.33*s2db + 2.0)
            endif
 
            if(nxant.ne.0) then
@@ -455,7 +451,6 @@ subroutine map65a(dd,ss,savg,newdat,nutc,fcenter,ntol,idphi,nfa,nfb,        &
            cmode='A '
            if(mode65.eq.2) cmode='B '
            if(mode65.eq.4) cmode='C '
-           if(nfast.eq.2) cmode(2:2)='2'
            write(26,1014) f0,ndf,ndf0,ndf1,ndf2,dt,npol,nsync1,       &
                 nsync2,nutc,decoded,cp,cmode
            write(21,1014) f0,ndf,ndf0,ndf1,ndf2,dt,npol,nsync1,       &
diff --git a/libm65/symspec.f90 b/libm65/symspec.f90
index 9fe6d7a32..f7652ca06 100644
--- a/libm65/symspec.f90
+++ b/libm65/symspec.f90
@@ -1,4 +1,4 @@
-subroutine symspec(k,nfast,nxpol,ndiskdat,nb,nbslider,idphi,nfsample,    &
+subroutine symspec(k,nxpol,ndiskdat,nb,nbslider,idphi,nfsample,    &
      fgreen,iqadjust,iqapply,gainx,gainy,phasex,phasey,rejectx,rejecty,  &
      pxdb,pydb,ssz5a,nkhz,ihsym,nzap,slimit,lstrong)
 
@@ -34,6 +34,7 @@ subroutine symspec(k,nfast,nxpol,ndiskdat,nb,nbslider,idphi,nfsample,    &
   data rms/999.0/,k0/99999999/,nadjx/0/,nadjy/0/
   save
 
+  nfast=1
   if(k.gt.5751000) go to 999
   if(k.lt.NFFT) then
      ihsym=0
diff --git a/mainwindow.cpp b/mainwindow.cpp
index a9caf54ec..942c9cf72 100644
--- a/mainwindow.cpp
+++ b/mainwindow.cpp
@@ -551,7 +551,7 @@ void MainWindow::dataSink(int k)
   fgreen=(float)g_pWideGraph->fGreen();
   nadj++;
   if(m_adjustIQ==0) nadj=0;
-  symspec_(&k, &m_nfast, &nxpol, &ndiskdat, &nb, &m_NBslider, &m_dPhi,
+  symspec_(&k, &nxpol, &ndiskdat, &nb, &m_NBslider, &m_dPhi,
            &nfsample, &fgreen, &m_adjustIQ, &m_applyIQcal,
            &m_gainx, &m_gainy, &m_phasex, &m_phasey, &rejectx, &rejecty,
            &px, &py, s, &nkhz, &ihsym, &nzap, &slimit, lstrong);
@@ -1484,7 +1484,7 @@ void MainWindow::guiUpdate()
     double samfac=1.0;
 
     if(m_modeTx=="JT65") {
-      gen65_(message,&mode65,&m_nfast,&samfac,&nsendingsh,msgsent,iwave,
+      gen65_(message,&mode65,&samfac,&nsendingsh,msgsent,iwave,
              &nwave,len1,len1);
     } else {
       if(m_modeQRA64==5) ntxFreq=600;
@@ -1937,7 +1937,7 @@ void MainWindow::msgtype(QString t, QLineEdit* tx)                //msgtype()
   int i1=t.indexOf(" OOO");
   QByteArray s=t.toUpper().toLocal8Bit();
   ba2msg(s,message);
-  gen65_(message,&mode65,&m_nfast,&samfac,&nsendingsh,msgsent,iwave,
+  gen65_(message,&mode65,&samfac,&nsendingsh,msgsent,iwave,
          &mwave,len1,len1);
 
   QPalette p(tx->palette());
diff --git a/mainwindow.h b/mainwindow.h
index 65a6a4578..68c8e2508 100644
--- a/mainwindow.h
+++ b/mainwindow.h
@@ -289,14 +289,14 @@ extern void getDev(int* numDevices,char hostAPI_DeviceName[][50],
 
 extern "C" {
 //----------------------------------------------------- C and Fortran routines
-  void symspec_(int* k, int* nfast, int* nxpol, int* ndiskdat, int* nb,
+  void symspec_(int* k, int* nxpol, int* ndiskdat, int* nb,
                 int* m_NBslider, int* idphi, int* nfsample, float* fgreen,
                 int* iqadjust, int* iqapply, float* gainx, float* gainy,
                 float* phasex, float* phasey, float* rejectx, float* rejecty,
                 float* px, float* py, float s[], int* nkhz, int* nhsym,
                 int* nzap, float* slimit, uchar lstrong[]);
 
-  void gen65_(char* msg, int* mode65, int* nfast, double* samfac,
+  void gen65_(char* msg, int* mode65, double* samfac,
               int* nsendingsh, char* msgsent, short iwave[], int* nwave,
               int len1, int len2);