| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | module jt65_decode
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |   integer, parameter :: NSZ=3413, NZMAX=60*12000
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |   type :: jt65_decoder
 | 
					
						
							|  |  |  |      procedure(jt65_decode_callback), pointer :: callback => null()
 | 
					
						
							|  |  |  |    contains
 | 
					
						
							|  |  |  |      procedure :: decode
 | 
					
						
							|  |  |  |   end type jt65_decoder
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | ! Callback function to be called with each decode
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |   abstract interface
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |      subroutine jt65_decode_callback(this,sync,snr,dt,freq,drift,     &
 | 
					
						
							|  |  |  |           nflip,width,decoded,ft,qual,nsmo,nsum,minsync)
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |        import jt65_decoder
 | 
					
						
							|  |  |  |        implicit none
 | 
					
						
							|  |  |  |        class(jt65_decoder), intent(inout) :: this
 | 
					
						
							|  |  |  |        real, intent(in) :: sync
 | 
					
						
							|  |  |  |        integer, intent(in) :: snr
 | 
					
						
							|  |  |  |        real, intent(in) :: dt
 | 
					
						
							|  |  |  |        integer, intent(in) :: freq
 | 
					
						
							|  |  |  |        integer, intent(in) :: drift
 | 
					
						
							| 
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 |  |  |        integer, intent(in) :: nflip
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |        real, intent(in) :: width
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |        character(len=22), intent(in) :: decoded
 | 
					
						
							|  |  |  |        integer, intent(in) :: ft
 | 
					
						
							|  |  |  |        integer, intent(in) :: qual
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  |        integer, intent(in) :: nsmo
 | 
					
						
							|  |  |  |        integer, intent(in) :: nsum
 | 
					
						
							|  |  |  |        integer, intent(in) :: minsync
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |      end subroutine jt65_decode_callback
 | 
					
						
							|  |  |  |   end interface
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | contains
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  |   subroutine decode(this,callback,dd0,npts,newdat,nutc,nf1,nf2,nfqso,     &
 | 
					
						
							|  |  |  |        ntol,nsubmode,minsync,nagain,n2pass,nrobust,ntrials,naggressive,   &
 | 
					
						
							| 
									
										
										
										
											2017-11-04 17:03:56 +00:00
										 |  |  |        ndepth,emedelay,clearave,mycall,hiscall,hisgrid,nexp_decode,       &
 | 
					
						
							|  |  |  |        nQSOProgress,ljt65apon)
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | !  Process dd0() data to find and decode JT65 signals.
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-10 14:25:22 +00:00
										 |  |  |     use jt65_mod
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     use timer_module, only: timer
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     include 'constants.f90'
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     class(jt65_decoder), intent(inout) :: this
 | 
					
						
							|  |  |  |     procedure(jt65_decode_callback) :: callback
 | 
					
						
							| 
									
										
										
										
											2016-12-22 20:51:27 +00:00
										 |  |  |     real, intent(in) :: dd0(NZMAX),emedelay
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     integer, intent(in) :: npts, nutc, nf1, nf2, nfqso, ntol     &
 | 
					
						
							|  |  |  |          , nsubmode, minsync, n2pass, ntrials, naggressive, ndepth      &
 | 
					
						
							| 
									
										
										
										
											2017-11-04 17:03:56 +00:00
										 |  |  |          , nexp_decode, nQSOProgress
 | 
					
						
							|  |  |  |     logical, intent(in) :: newdat, nagain, nrobust, clearave, ljt65apon
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     character(len=12), intent(in) :: mycall, hiscall
 | 
					
						
							|  |  |  |     character(len=6), intent(in) :: hisgrid
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     real dd(NZMAX)
 | 
					
						
							| 
									
										
										
										
											2017-10-22 00:09:01 +00:00
										 |  |  |     real ss(552,NSZ)
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     real savg(NSZ)
 | 
					
						
							|  |  |  |     real a(5)
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     character*22 decoded,decoded0,avemsg,deepave
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     type candidate
 | 
					
						
							|  |  |  |        real freq
 | 
					
						
							|  |  |  |        real dt
 | 
					
						
							|  |  |  |        real sync
 | 
					
						
							| 
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 |  |  |        real flip
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     end type candidate
 | 
					
						
							|  |  |  |     type(candidate) ca(300)
 | 
					
						
							|  |  |  |     type accepted_decode
 | 
					
						
							|  |  |  |        real freq
 | 
					
						
							|  |  |  |        real dt
 | 
					
						
							|  |  |  |        real sync
 | 
					
						
							|  |  |  |        character*22 decoded
 | 
					
						
							|  |  |  |     end type accepted_decode
 | 
					
						
							|  |  |  |     type(accepted_decode) dec(50)
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |     logical :: first_time,prtavg,single_decode,bVHF,clear_avg65
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     integer h0(0:11),d0(0:11)
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     real r0(0:11)
 | 
					
						
							|  |  |  |     common/decstats/ntry65a,ntry65b,n65a,n65b,num9,numfano
 | 
					
						
							|  |  |  |     common/steve/thresh0
 | 
					
						
							| 
									
										
										
										
											2017-10-22 00:09:01 +00:00
										 |  |  |     common/sync/ss
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | !            0  1  2  3  4  5  6  7  8  9 10 11
 | 
					
						
							|  |  |  |     data h0/41,42,43,43,44,45,46,47,48,48,49,49/
 | 
					
						
							|  |  |  |     data d0/71,72,73,74,76,77,78,80,81,82,83,83/
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | !             0    1    2    3    4    5    6    7    8    9   10   11
 | 
					
						
							|  |  |  |     data r0/0.70,0.72,0.74,0.76,0.78,0.80,0.82,0.84,0.86,0.88,0.90,0.90/
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |     data nutc0/-999/,nfreq0/-999/,nsave/0/,clear_avg65/.true./
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     save
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     this%callback => callback
 | 
					
						
							| 
									
										
										
										
											2020-03-17 15:50:21 -04:00
										 |  |  |     first_time=nrobust                !Silence compiler warning
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |     first_time=newdat
 | 
					
						
							|  |  |  |     dd=dd0
 | 
					
						
							|  |  |  |     ndecoded=0
 | 
					
						
							| 
									
										
										
										
											2020-04-19 18:56:16 -04:00
										 |  |  |     ndecoded0=0
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |     if(nsubmode.ge.100) then
 | 
					
						
							| 
									
										
										
										
											2016-07-02 12:48:27 +00:00
										 |  |  | ! This is QRA64 mode
 | 
					
						
							| 
									
										
										
										
											2016-07-28 15:18:06 +00:00
										 |  |  |        mode64=2**(nsubmode-100)
 | 
					
						
							| 
									
										
										
										
											2020-03-19 13:13:33 -04:00
										 |  |  |        call qra64a(dd,npts,nf1,nf2,nfqso,ntol,mode64,minsync,ndepth,         &
 | 
					
						
							| 
									
										
										
										
											2017-06-07 21:03:38 +00:00
										 |  |  |             emedelay,mycall,hiscall,hisgrid,sync,nsnr,dtx,nfreq,decoded,nft)
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  |        if (associated(this%callback)) then
 | 
					
						
							|  |  |  |           ndrift=0
 | 
					
						
							|  |  |  |           nflip=1
 | 
					
						
							|  |  |  |           width=1.0
 | 
					
						
							|  |  |  |           nsmo=0
 | 
					
						
							|  |  |  |           nqual=0
 | 
					
						
							|  |  |  |           call this%callback(sync,nsnr,dtx,nfreq,ndrift,  &
 | 
					
						
							|  |  |  |                nflip,width,decoded,nft,nqual,nsmo,1,minsync)
 | 
					
						
							|  |  |  |        end if
 | 
					
						
							|  |  |  |        go to 900
 | 
					
						
							|  |  |  |     endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-11-24 02:38:14 +00:00
										 |  |  |     single_decode=iand(nexp_decode,32).ne.0 .or. nagain
 | 
					
						
							|  |  |  |     bVHF=iand(nexp_decode,64).ne.0
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2020-04-19 18:56:16 -04:00
										 |  |  |     if(bVHF) then
 | 
					
						
							| 
									
										
										
										
											2017-11-24 02:38:14 +00:00
										 |  |  |       nvec=ntrials
 | 
					
						
							|  |  |  |       npass=1
 | 
					
						
							|  |  |  |       if(n2pass.gt.1) npass=2
 | 
					
						
							|  |  |  |     else
 | 
					
						
							|  |  |  |       nvec=1000
 | 
					
						
							| 
									
										
										
										
											2017-11-24 02:38:15 +00:00
										 |  |  |       if(ndepth.eq.1) then
 | 
					
						
							|  |  |  |          npass=2
 | 
					
						
							|  |  |  |          nvec=100
 | 
					
						
							|  |  |  |       elseif(ndepth.eq.2) then
 | 
					
						
							|  |  |  |          npass=2
 | 
					
						
							|  |  |  |          nvec=1000
 | 
					
						
							|  |  |  |       else 
 | 
					
						
							|  |  |  |          npass=4
 | 
					
						
							| 
									
										
										
										
											2017-11-28 20:46:00 +00:00
										 |  |  |          nvec=1000
 | 
					
						
							| 
									
										
										
										
											2017-11-24 02:38:15 +00:00
										 |  |  |       endif
 | 
					
						
							| 
									
										
										
										
											2017-11-24 02:38:14 +00:00
										 |  |  |     endif
 | 
					
						
							| 
									
										
										
										
											2017-10-22 00:09:01 +00:00
										 |  |  |     do ipass=1,npass 
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |        first_time=.true.
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |        if(ipass.eq.1) then                        !First-pass parameters
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |           thresh0=2.5
 | 
					
						
							|  |  |  |           nsubtract=1
 | 
					
						
							| 
									
										
										
										
											2017-10-22 00:09:01 +00:00
										 |  |  |           nrob=0
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |        elseif( ipass.eq.2 ) then                  !Second-pass parameters
 | 
					
						
							| 
									
										
										
										
											2017-10-22 00:09:01 +00:00
										 |  |  |           thresh0=2.0
 | 
					
						
							|  |  |  |           nsubtract=1
 | 
					
						
							|  |  |  |           nrob=0
 | 
					
						
							|  |  |  |        elseif( ipass.eq.3 ) then 
 | 
					
						
							|  |  |  |           thresh0=2.0
 | 
					
						
							|  |  |  |           nsubtract=1
 | 
					
						
							|  |  |  |           nrob=0
 | 
					
						
							|  |  |  |        elseif( ipass.eq.4 ) then 
 | 
					
						
							|  |  |  |           thresh0=2.0
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |           nsubtract=0
 | 
					
						
							| 
									
										
										
										
											2017-10-22 00:09:01 +00:00
										 |  |  |           nrob=1
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							|  |  |  |        if(npass.eq.1) then
 | 
					
						
							|  |  |  |          nsubtract=0
 | 
					
						
							|  |  |  |          thresh0=2.0
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |        endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |        call timer('symsp65 ',0)
 | 
					
						
							|  |  |  |        ss=0.
 | 
					
						
							| 
									
										
										
										
											2017-10-22 00:09:01 +00:00
										 |  |  |        call symspec65(dd,npts,nqsym,savg)    !Get normalized symbol spectra
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |        call timer('symsp65 ',1)
 | 
					
						
							|  |  |  |        nfa=nf1
 | 
					
						
							|  |  |  |        nfb=nf2
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | !### Q: should either of the next two uses of "single_decode" be "bVHF" instead?       
 | 
					
						
							|  |  |  |        if(single_decode .or. (bVHF .and. ntol.lt.1000)) then
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |           nfa=max(200,nfqso-ntol)
 | 
					
						
							|  |  |  |           nfb=min(4000,nfqso+ntol)
 | 
					
						
							|  |  |  |           thresh0=1.0
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2016-03-17 18:52:06 +00:00
										 |  |  |        df=12000.0/8192.0                     !df = 1.465 Hz
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  |        if(bVHF) then
 | 
					
						
							| 
									
										
										
										
											2020-06-01 11:24:24 -04:00
										 |  |  |           ia=max(1,nint((nfa-100)/df))
 | 
					
						
							|  |  |  |           ib=min(NSZ,nint((nfb+100)/df))
 | 
					
						
							| 
									
										
										
										
											2016-03-17 18:52:06 +00:00
										 |  |  |           nz=ib-ia+1
 | 
					
						
							|  |  |  |           call lorentzian(savg(ia),nz,a)
 | 
					
						
							|  |  |  |           baseline=a(1)
 | 
					
						
							|  |  |  |           amp=a(2)
 | 
					
						
							|  |  |  |           f0=(a(3)+ia-1)*df
 | 
					
						
							|  |  |  |           width=a(4)*df
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |        ncand=0
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  |        call timer('sync65  ',0)
 | 
					
						
							| 
									
										
										
										
											2020-03-19 13:20:07 -04:00
										 |  |  |        call sync65(nfa,nfb,ntol,nqsym,ca,ncand,nrob,bVHF)
 | 
					
						
							| 
									
										
										
										
											2020-04-19 18:56:16 -04:00
										 |  |  |        ncand=min(ncand,50/ipass)
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  |        call timer('sync65  ',1)
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  |        mode65=2**nsubmode
 | 
					
						
							| 
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 |  |  |        nflip=1
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |        nqd=0
 | 
					
						
							| 
									
										
										
										
											2016-05-04 18:44:05 +00:00
										 |  |  |        decoded='                      '
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |        decoded0=""
 | 
					
						
							|  |  |  |        freq0=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |        prtavg=.false.
 | 
					
						
							| 
									
										
										
										
											2016-03-11 17:03:41 +00:00
										 |  |  |        if(.not.nagain) nsum=0
 | 
					
						
							| 
									
										
										
										
											2016-04-06 17:11:19 +00:00
										 |  |  |        if(clearave) then
 | 
					
						
							| 
									
										
										
										
											2016-03-11 17:03:41 +00:00
										 |  |  |           nsum=0
 | 
					
						
							|  |  |  |           nsave=0
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |           clear_avg65=.true.
 | 
					
						
							| 
									
										
										
										
											2016-03-11 17:03:41 +00:00
										 |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2020-04-09 10:51:35 -04:00
										 |  |  |        if(bVHF) then
 | 
					
						
							| 
									
										
										
										
											2016-10-18 17:27:06 +00:00
										 |  |  | ! Be sure to search for shorthand message at nfqso +/- ntol
 | 
					
						
							| 
									
										
										
										
											2020-04-09 10:51:35 -04:00
										 |  |  |           if(ncand.lt.300) ncand=ncand+1
 | 
					
						
							|  |  |  |           ca(ncand)%sync=5.0
 | 
					
						
							|  |  |  |           ca(ncand)%dt=2.5
 | 
					
						
							|  |  |  |           ca(ncand)%freq=nfqso
 | 
					
						
							| 
									
										
										
										
											2020-04-18 11:45:44 -04:00
										 |  |  |           ca(ncand)%flip=0
 | 
					
						
							| 
									
										
										
										
											2020-04-09 10:51:35 -04:00
										 |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |        do icand=1,ncand
 | 
					
						
							|  |  |  |           sync1=ca(icand)%sync
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  |           dtx=ca(icand)%dt
 | 
					
						
							|  |  |  |           freq=ca(icand)%freq
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  |           if(bVHF) then
 | 
					
						
							| 
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 |  |  |              flip=ca(icand)%flip
 | 
					
						
							| 
									
										
										
										
											2020-03-17 15:50:21 -04:00
										 |  |  |              nflip=int(flip)
 | 
					
						
							| 
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 |  |  |           endif
 | 
					
						
							| 
									
										
										
										
											2016-05-04 18:44:05 +00:00
										 |  |  |           if(sync1.lt.float(minsync)) nflip=0
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |           if(ipass.eq.1) ntry65a=ntry65a + 1
 | 
					
						
							|  |  |  |           if(ipass.eq.2) ntry65b=ntry65b + 1
 | 
					
						
							|  |  |  |           call timer('decod65a',0)
 | 
					
						
							| 
									
										
										
										
											2016-05-24 16:00:00 +00:00
										 |  |  |           nft=0
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  |           nspecial=0
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |           call decode65a(dd,npts,first_time,nqd,freq,nflip,mode65,nvec,     &
 | 
					
						
							| 
									
										
										
										
											2017-11-04 00:40:08 +00:00
										 |  |  |                naggressive,ndepth,ntol,mycall,hiscall,hisgrid,nQSOProgress, &
 | 
					
						
							| 
									
										
										
										
											2020-03-19 11:00:21 -04:00
										 |  |  |                ljt65apon,bVHF,sync2,a,dtx,nft,nspecial,qual,                &
 | 
					
						
							| 
									
										
										
										
											2016-05-04 18:16:09 +00:00
										 |  |  |                nhist,nsmo,decoded)
 | 
					
						
							| 
									
										
										
										
											2020-04-09 13:56:35 -04:00
										 |  |  |           call timer('decod65a',1)
 | 
					
						
							| 
									
										
										
										
											2020-04-19 18:56:16 -04:00
										 |  |  | 
 | 
					
						
							|  |  |  |           if(.not.bVHF) then   
 | 
					
						
							|  |  |  |              if(abs(a(1)).gt.10.0/ipass) cycle
 | 
					
						
							|  |  |  |              ibad=0
 | 
					
						
							|  |  |  |              if(abs(a(1)).gt.5.0) ibad=1
 | 
					
						
							|  |  |  |              if(abs(a(2)).gt.2.0) ibad=ibad+1
 | 
					
						
							|  |  |  |              if(abs(dtx-1.0).gt.2.5) ibad=ibad+1
 | 
					
						
							|  |  |  |              if(ibad.ge.2) cycle
 | 
					
						
							|  |  |  |           endif
 | 
					
						
							|  |  |  |           
 | 
					
						
							| 
									
										
										
										
											2020-04-09 13:56:35 -04:00
										 |  |  |           if(nspecial.eq.0 .and. sync1.eq.5.0 .and. dtx.eq.2.5) cycle
 | 
					
						
							| 
									
										
										
										
											2016-05-04 18:16:09 +00:00
										 |  |  |           if(nspecial.eq.2) decoded='RO'
 | 
					
						
							|  |  |  |           if(nspecial.eq.3) decoded='RRR'
 | 
					
						
							|  |  |  |           if(nspecial.eq.4) decoded='73'
 | 
					
						
							| 
									
										
										
										
											2016-05-03 20:30:49 +00:00
										 |  |  |           if(sync1.lt.float(minsync) .and.                                  &
 | 
					
						
							|  |  |  |                decoded.eq.'                      ') nflip=0
 | 
					
						
							| 
									
										
										
										
											2016-03-23 13:55:40 +00:00
										 |  |  |           if(nft.ne.0) nsum=1
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |           
 | 
					
						
							| 
									
										
										
										
											2016-03-10 19:39:24 +00:00
										 |  |  |           nhard_min=param(1)
 | 
					
						
							|  |  |  |           nrtt1000=param(4)
 | 
					
						
							|  |  |  |           ntotal_min=param(5)
 | 
					
						
							|  |  |  |           nsmo=param(9)
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |           
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |           nfreq=nint(freq+a(1))
 | 
					
						
							|  |  |  |           ndrift=nint(2.0*a(2))
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  |           if(bVHF) then
 | 
					
						
							| 
									
										
										
										
											2018-01-01 22:11:36 +00:00
										 |  |  |             xtmp=10**((sync1+16.0)/10.0) ! sync comes to us in dB
 | 
					
						
							|  |  |  |             s2db=1.1*db(xtmp)+1.4*(dB(width)-4.3)-52.0 
 | 
					
						
							|  |  |  | !             s2db=sync1 - 30.0 + db(width/3.3)       !### VHF/UHF/microwave
 | 
					
						
							| 
									
										
										
										
											2016-05-04 18:16:09 +00:00
										 |  |  |              if(nspecial.gt.0) s2db=sync2
 | 
					
						
							| 
									
										
										
										
											2016-03-19 00:16:09 +00:00
										 |  |  |           else
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |              s2db=10.0*log10(sync2) - 35             !### Empirical (HF) 
 | 
					
						
							| 
									
										
										
										
											2016-03-19 00:16:09 +00:00
										 |  |  |           endif
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  |           nsnr=nint(s2db)
 | 
					
						
							|  |  |  |           if(nsnr.lt.-30) nsnr=-30
 | 
					
						
							|  |  |  |           if(nsnr.gt.-1) nsnr=-1
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:03:11 +00:00
										 |  |  |           nftt=0
 | 
					
						
							| 
									
										
										
										
											2017-11-05 14:44:15 +00:00
										 |  |  | !********* DOES THIS STILL WORK WHEN NFT INCLUDES # OF AP SYMBOLS USED??
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |           if(nft.ne.1 .and. iand(ndepth,16).eq.16 .and.                    &
 | 
					
						
							|  |  |  |                sync1.ge.float(minsync) .and. (.not.prtavg)) then
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  | ! Single-sequence FT decode failed, so try for an average FT decode.
 | 
					
						
							|  |  |  |              if(nutc.ne.nutc0 .or. abs(nfreq-nfreq0).gt.ntol) then
 | 
					
						
							|  |  |  | ! This is a new minute or a new frequency, so call avg65.
 | 
					
						
							|  |  |  |                 nutc0=nutc
 | 
					
						
							|  |  |  |                 nfreq0=nfreq
 | 
					
						
							|  |  |  |                 nsave=nsave+1
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  |                 nsave=mod(nsave-1,64)+1
 | 
					
						
							| 
									
										
										
										
											2016-05-24 16:00:00 +00:00
										 |  |  |                 call avg65(nutc,nsave,sync1,dtx,nflip,nfreq,mode65,ntol,     &
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |                      ndepth,nagain,ntrials,naggressive,clear_avg65,neme,     &
 | 
					
						
							|  |  |  |                      mycall,hiscall,hisgrid,nftt,avemsg,qave,deepave,nsum,   &
 | 
					
						
							|  |  |  |                      ndeepave,nQSOProgress,ljt65apon)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |                 nsmo=param(9)
 | 
					
						
							| 
									
										
										
										
											2020-03-17 15:50:21 -04:00
										 |  |  |                 nqave=int(qave)
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |                 if (associated(this%callback) .and.nftt.ge.1 .and. nsum.ge.2) then
 | 
					
						
							|  |  |  | ! Display a decoded message obtained by averaging 2 or more transmissions
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |                    call this%callback(sync1,nsnr,dtx-1.0,nfreq,ndrift,  &
 | 
					
						
							|  |  |  |                         nflip,width,avemsg,nftt,nqave,nsmo,nsum,minsync)
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  |                    prtavg=.true.
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |                 end if
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |              endif
 | 
					
						
							|  |  |  |           endif
 | 
					
						
							| 
									
										
										
										
											2016-03-11 16:26:06 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |           if(nftt.eq.0) go to 5
 | 
					
						
							|  |  |  | !          if(nftt.eq.1) then
 | 
					
						
							|  |  |  | !!             nft=1
 | 
					
						
							|  |  |  | !             decoded=avemsg
 | 
					
						
							|  |  |  | !             go to 5
 | 
					
						
							|  |  |  | !          endif
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |           n=naggressive
 | 
					
						
							|  |  |  |           rtt=0.001*nrtt1000
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |           if(nft.lt.2 .and. minsync.ge.0 .and. nspecial.eq.0 .and. .not.bVHF) then
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |              if(nhard_min.gt.50) cycle
 | 
					
						
							|  |  |  |              if(nhard_min.gt.h0(n)) cycle
 | 
					
						
							|  |  |  |              if(ntotal_min.gt.d0(n)) cycle
 | 
					
						
							|  |  |  |              if(rtt.gt.r0(n)) cycle
 | 
					
						
							|  |  |  |           endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  | 5         continue
 | 
					
						
							|  |  |  |           if(decoded.eq.decoded0 .and. abs(freq-freq0).lt. 3.0 .and.    &
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |                minsync.ge.0) cycle                  !Don't display dupes
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  | !          if(decoded.ne.'                      ' .or. minsync.lt.0) then
 | 
					
						
							|  |  |  |           if(decoded.ne.'                      ' .or. bVHF) then
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |              if(nsubtract.eq.1) then
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |                 call timer('subtr65 ',0)
 | 
					
						
							|  |  |  |                 call subtract65(dd,npts,freq,dtx)
 | 
					
						
							|  |  |  |                 call timer('subtr65 ',1)
 | 
					
						
							|  |  |  |              endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |              ndupe=0 ! de-dedupe
 | 
					
						
							|  |  |  |              do i=1, ndecoded
 | 
					
						
							|  |  |  |                 if(decoded==dec(i)%decoded) then
 | 
					
						
							|  |  |  |                    ndupe=1
 | 
					
						
							|  |  |  |                    exit
 | 
					
						
							|  |  |  |                 endif
 | 
					
						
							|  |  |  |              enddo
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |              if(ndupe.ne.1 .and. ((sync1.ge.float(minsync)) .or. bVHF)) then
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |                 if(ipass.eq.1) n65a=n65a + 1
 | 
					
						
							|  |  |  |                 if(ipass.eq.2) n65b=n65b + 1
 | 
					
						
							| 
									
										
										
										
											2016-10-24 14:23:21 +00:00
										 |  |  |                 if(ndecoded.lt.50) ndecoded=ndecoded+1
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |                 dec(ndecoded)%freq=freq+a(1)
 | 
					
						
							|  |  |  |                 dec(ndecoded)%dt=dtx
 | 
					
						
							|  |  |  |                 dec(ndecoded)%sync=sync2
 | 
					
						
							|  |  |  |                 dec(ndecoded)%decoded=decoded
 | 
					
						
							| 
									
										
										
										
											2020-03-17 15:50:21 -04:00
										 |  |  |                 nqual=min(int(qual),9999)
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |                 if(associated(this%callback)) then
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |                    call this%callback(sync1,nsnr,dtx-1.0,nfreq,ndrift,  &
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |                         nflip,width,decoded,nft,nqual,nsmo,1,minsync)
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |                 end if
 | 
					
						
							|  |  |  |              endif
 | 
					
						
							|  |  |  |              decoded0=decoded
 | 
					
						
							|  |  |  |              freq0=freq
 | 
					
						
							|  |  |  |              if(decoded0.eq.'                      ') decoded0='*'
 | 
					
						
							| 
									
										
										
										
											2020-04-19 18:56:16 -04:00
										 |  |  |              if(single_decode .and. ndecoded.gt.0) go to 900
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |           endif
 | 
					
						
							| 
									
										
										
										
											2020-04-19 18:56:16 -04:00
										 |  |  |        enddo   ! icand
 | 
					
						
							|  |  |  |        if(ipass.gt.1 .and. ndecoded.eq.ndecoded0) exit
 | 
					
						
							|  |  |  |        ndecoded0=ndecoded
 | 
					
						
							|  |  |  |     enddo   ! ipass
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  | 900 return
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  |   end subroutine decode
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-24 16:00:00 +00:00
										 |  |  |   subroutine avg65(nutc,nsave,snrsync,dtxx,nflip,nfreq,mode65,ntol,ndepth,    &
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |        nagain, ntrials,naggressive,clear_avg65,neme,mycall,hiscall,hisgrid,   &
 | 
					
						
							|  |  |  |        nftt,avemsg,qave,deepave,nsum,ndeepave,nQSOProgress,ljt65apon)
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  | ! Decodes averaged JT65 data
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-10 14:25:22 +00:00
										 |  |  |     use jt65_mod
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     parameter (MAXAVE=64)
 | 
					
						
							|  |  |  |     character*22 avemsg,deepave,deepbest
 | 
					
						
							|  |  |  |     character mycall*12,hiscall*12,hisgrid*6
 | 
					
						
							|  |  |  |     character*1 csync,cused(64)
 | 
					
						
							| 
									
										
										
										
											2016-05-24 16:00:00 +00:00
										 |  |  |     logical nagain
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     integer iused(64)
 | 
					
						
							|  |  |  | ! Accumulated data for message averaging
 | 
					
						
							|  |  |  |     integer iutc(MAXAVE)
 | 
					
						
							|  |  |  |     integer nfsave(MAXAVE)
 | 
					
						
							|  |  |  |     integer nflipsave(MAXAVE)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |     real s1b(-255:256,126)
 | 
					
						
							|  |  |  |     real s1save(-255:256,126,MAXAVE)
 | 
					
						
							|  |  |  |     real s2(66,126)
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     real s3save(64,63,MAXAVE)
 | 
					
						
							|  |  |  |     real s3b(64,63)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |     real s3c(64,63)
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     real dtsave(MAXAVE)
 | 
					
						
							|  |  |  |     real syncsave(MAXAVE)
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |     logical first,clear_avg65,ljt65apon
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     data first/.true./
 | 
					
						
							|  |  |  |     save
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |     if(first .or. clear_avg65) then
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |        iutc=-1
 | 
					
						
							|  |  |  |        nfsave=0
 | 
					
						
							|  |  |  |        dtdiff=0.2
 | 
					
						
							| 
									
										
										
										
											2016-03-21 16:03:11 +00:00
										 |  |  |        s3save=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |        s1save=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-10 14:25:22 +00:00
										 |  |  |        nsave=1           !### ???
 | 
					
						
							| 
									
										
										
										
											2016-06-09 19:39:48 +00:00
										 |  |  | ! Silence compiler warnings
 | 
					
						
							|  |  |  |        if(nagain .and. ndeepave.eq.-99 .and. neme.eq.-99) stop
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |        first=.false.
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |        clear_avg65=.false.
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     do i=1,64
 | 
					
						
							| 
									
										
										
										
											2016-05-24 16:00:00 +00:00
										 |  |  |        if(iutc(i).lt.0) exit
 | 
					
						
							|  |  |  |        if(nutc.eq.iutc(i) .and. abs(nfreq-nfsave(i)).le.ntol) go to 10
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  | ! Save data for message averaging
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     iutc(nsave)=nutc
 | 
					
						
							|  |  |  |     syncsave(nsave)=snrsync
 | 
					
						
							|  |  |  |     dtsave(nsave)=dtxx
 | 
					
						
							|  |  |  |     nfsave(nsave)=nfreq
 | 
					
						
							|  |  |  |     nflipsave(nsave)=nflip
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |     s1save(-255:256,1:126,nsave)=s1
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     s3save(1:64,1:63,nsave)=s3a
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |     avemsg='                      '
 | 
					
						
							|  |  |  |     deepbest='                      '
 | 
					
						
							|  |  |  |     nfttbest=0
 | 
					
						
							| 
									
										
										
										
											2020-04-08 16:56:28 -04:00
										 |  |  |     
 | 
					
						
							| 
									
										
										
										
											2016-03-10 14:25:22 +00:00
										 |  |  | 10  syncsum=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     dtsum=0.
 | 
					
						
							|  |  |  |     nfsum=0
 | 
					
						
							|  |  |  |     nsum=0
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |     s1b=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-10 14:25:22 +00:00
										 |  |  |     s3b=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |     s3c=0.
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |     do i=1,MAXAVE                               !Consider all saved spectra
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |        cused(i)='.'
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |        if(iutc(i).lt.0) exit
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |        if(mod(iutc(i),2).ne.mod(nutc,2)) cycle  !Use only same (odd/even) seq
 | 
					
						
							|  |  |  |        if(abs(dtxx-dtsave(i)).gt.dtdiff) cycle  !DT must match
 | 
					
						
							|  |  |  |        if(abs(nfreq-nfsave(i)).gt.ntol) cycle   !Freq must match
 | 
					
						
							| 
									
										
										
										
											2020-05-08 10:32:23 -04:00
										 |  |  |        if(nflipsave(i).eq.0) cycle              !No sync
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |        if(nflip.ne.nflipsave(i)) cycle          !Sync type (*/#) must match
 | 
					
						
							| 
									
										
										
										
											2020-05-08 10:32:23 -04:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |        s3b=s3b + s3save(1:64,1:63,i)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |        s1b=s1b + s1save(-255:256,1:126,i)
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |        syncsum=syncsum + syncsave(i)
 | 
					
						
							|  |  |  |        dtsum=dtsum + dtsave(i)
 | 
					
						
							|  |  |  |        nfsum=nfsum + nfsave(i)
 | 
					
						
							|  |  |  |        cused(i)='$'
 | 
					
						
							|  |  |  |        nsum=nsum+1
 | 
					
						
							|  |  |  |        iused(nsum)=i
 | 
					
						
							|  |  |  |     enddo
 | 
					
						
							|  |  |  |     if(nsum.lt.64) iused(nsum+1)=0
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     syncave=0.
 | 
					
						
							|  |  |  |     dtave=0.
 | 
					
						
							|  |  |  |     fave=0.
 | 
					
						
							|  |  |  |     if(nsum.gt.0) then
 | 
					
						
							|  |  |  |        syncave=syncsum/nsum
 | 
					
						
							|  |  |  |        dtave=dtsum/nsum
 | 
					
						
							|  |  |  |        fave=float(nfsum)/nsum
 | 
					
						
							|  |  |  |     endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     do i=1,nsave
 | 
					
						
							| 
									
										
										
										
											2020-05-08 10:32:23 -04:00
										 |  |  |        csync=' '
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |        if(nflipsave(i).lt.0.0) csync='#'
 | 
					
						
							| 
									
										
										
										
											2020-05-08 10:32:23 -04:00
										 |  |  |        if(nflipsave(i).gt.0.0) csync='*'
 | 
					
						
							| 
									
										
										
										
											2016-03-23 15:08:00 +00:00
										 |  |  |        write(14,1000) cused(i),iutc(i),syncsave(i),dtsave(i)-1.0,nfsave(i),csync
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  | 1000   format(a1,i5.4,f6.1,f6.2,i6,1x,a1)
 | 
					
						
							|  |  |  |     enddo
 | 
					
						
							| 
									
										
										
										
											2016-03-11 16:26:06 +00:00
										 |  |  |     if(nsum.lt.2) go to 900
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |     df=1378.125/512.0
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | ! Do the smoothing loop
 | 
					
						
							|  |  |  |     qualbest=0.
 | 
					
						
							|  |  |  |     minsmo=0
 | 
					
						
							|  |  |  |     maxsmo=0
 | 
					
						
							|  |  |  |     if(mode65.ge.2) then
 | 
					
						
							|  |  |  |        minsmo=nint(width/df)
 | 
					
						
							|  |  |  |        maxsmo=2*minsmo
 | 
					
						
							|  |  |  |     endif
 | 
					
						
							|  |  |  |     nn=0
 | 
					
						
							|  |  |  |     do ismo=minsmo,maxsmo
 | 
					
						
							| 
									
										
										
										
											2020-04-09 13:56:35 -04:00
										 |  |  |        nftt=0
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |        if(ismo.gt.0) then
 | 
					
						
							|  |  |  |           do j=1,126
 | 
					
						
							|  |  |  |              call smo121(s1b(-255,j),512)
 | 
					
						
							|  |  |  |              if(j.eq.1) nn=nn+1
 | 
					
						
							|  |  |  |              if(nn.ge.4) then
 | 
					
						
							|  |  |  |                 call smo121(s1b(-255,j),512)
 | 
					
						
							|  |  |  |                 if(j.eq.1) nn=nn+1
 | 
					
						
							|  |  |  |              endif
 | 
					
						
							|  |  |  |           enddo
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |        do i=1,66
 | 
					
						
							|  |  |  |           jj=i
 | 
					
						
							|  |  |  |           if(mode65.eq.2) jj=2*i-1
 | 
					
						
							|  |  |  |           if(mode65.eq.4) then
 | 
					
						
							|  |  |  |              ff=4*(i-1)*df - 355.297852
 | 
					
						
							|  |  |  |              jj=nint(ff/df)+1
 | 
					
						
							|  |  |  |           endif
 | 
					
						
							|  |  |  |           s2(i,1:126)=s1b(jj,1:126)
 | 
					
						
							|  |  |  |        enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |        do j=1,63
 | 
					
						
							|  |  |  |           k=mdat(j)                       !Points to data symbol
 | 
					
						
							|  |  |  |           if(nflip.lt.0) k=mdat2(j)
 | 
					
						
							|  |  |  |           do i=1,64
 | 
					
						
							|  |  |  |              s3c(i,j)=4.e-5*s2(i+2,k)
 | 
					
						
							|  |  |  |           enddo
 | 
					
						
							|  |  |  |        enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-25 18:19:25 +00:00
										 |  |  |        nadd=nsum*ismo
 | 
					
						
							| 
									
										
										
										
											2017-12-02 16:04:51 +00:00
										 |  |  |        call extract(s3c,nadd,mode65,ntrials,naggressive,ndepth,nflip,mycall, &
 | 
					
						
							| 
									
										
										
										
											2020-03-19 11:00:21 -04:00
										 |  |  |             hiscall,hisgrid,nQSOProgress,ljt65apon,ncount,nhist, &
 | 
					
						
							| 
									
										
										
										
											2017-12-02 16:04:51 +00:00
										 |  |  |             avemsg,ltext,nftt,qual)
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |        if(nftt.eq.1) then
 | 
					
						
							|  |  |  |           nsmo=ismo
 | 
					
						
							|  |  |  |           param(9)=nsmo
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |           go to 900
 | 
					
						
							| 
									
										
										
										
											2020-04-09 13:56:35 -04:00
										 |  |  |        else if(nftt.ge.2) then
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |           if(qual.gt.qualbest) then
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |              deepbest=avemsg
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |              qualbest=qual
 | 
					
						
							|  |  |  |              nnbest=nn
 | 
					
						
							|  |  |  |              nsmobest=ismo
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |              nfttbest=nftt
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |           endif
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							|  |  |  |     enddo
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |     if(nfttbest.eq.2) then
 | 
					
						
							|  |  |  |        avemsg=deepbest       !### ???
 | 
					
						
							|  |  |  |        deepave=deepbest
 | 
					
						
							|  |  |  |        qave=qualbest
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |        nsmo=nsmobest
 | 
					
						
							|  |  |  |        param(9)=nsmo
 | 
					
						
							| 
									
										
										
										
											2016-03-22 16:42:59 +00:00
										 |  |  |        nftt=nfttbest
 | 
					
						
							| 
									
										
										
										
											2016-03-21 19:11:38 +00:00
										 |  |  |     endif
 | 
					
						
							| 
									
										
										
										
											2016-03-11 16:26:06 +00:00
										 |  |  | 900 continue
 | 
					
						
							| 
									
										
										
										
											2020-04-09 15:30:12 -04:00
										 |  |  |     
 | 
					
						
							| 
									
										
										
										
											2016-03-08 21:04:05 +00:00
										 |  |  |     return
 | 
					
						
							|  |  |  |   end subroutine avg65
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-01-11 15:00:43 +00:00
										 |  |  | end module jt65_decode
 |