| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  | subroutine multimode_decoder(ss,id2,params,nfsample)
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-02-05 22:07:19 +00:00
										 |  |  |   !$ use omp_lib
 | 
					
						
							| 
									
										
										
										
											2015-12-27 15:40:57 +00:00
										 |  |  |   use prog_args
 | 
					
						
							|  |  |  |   use timer_module, only: timer
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |   use jt4_decode
 | 
					
						
							|  |  |  |   use jt65_decode
 | 
					
						
							|  |  |  |   use jt9_decode
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |   use ft8_decode
 | 
					
						
							| 
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   include 'jt9com.f90'
 | 
					
						
							| 
									
										
										
										
											2015-12-27 15:40:57 +00:00
										 |  |  |   include 'timer_common.inc'
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |   type, extends(jt4_decoder) :: counting_jt4_decoder
 | 
					
						
							|  |  |  |      integer :: decoded
 | 
					
						
							|  |  |  |   end type counting_jt4_decoder
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   type, extends(jt65_decoder) :: counting_jt65_decoder
 | 
					
						
							|  |  |  |      integer :: decoded
 | 
					
						
							|  |  |  |   end type counting_jt65_decoder
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   type, extends(jt9_decoder) :: counting_jt9_decoder
 | 
					
						
							|  |  |  |      integer :: decoded
 | 
					
						
							|  |  |  |   end type counting_jt9_decoder
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |   type, extends(ft8_decoder) :: counting_ft8_decoder
 | 
					
						
							|  |  |  |      integer :: decoded
 | 
					
						
							|  |  |  |   end type counting_ft8_decoder
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  |   real ss(184,NSMAX)
 | 
					
						
							| 
									
										
										
										
											2018-04-24 14:15:13 +00:00
										 |  |  |   logical baddata,newdat65,newdat9,single_decode,bVHF,bad0,newdat,ex
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  |   integer*2 id2(NTMAX*12000)
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   type(params_block) :: params
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  |   real*4 dd(NTMAX*12000)
 | 
					
						
							| 
									
										
										
										
											2018-05-19 20:41:27 +00:00
										 |  |  |   character(len=20) :: datetime
 | 
					
						
							|  |  |  |   character(len=12) :: mycall, hiscall
 | 
					
						
							|  |  |  |   character(len=6) :: mygrid, hisgrid
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  |   save
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |   type(counting_jt4_decoder) :: my_jt4
 | 
					
						
							|  |  |  |   type(counting_jt65_decoder) :: my_jt65
 | 
					
						
							|  |  |  |   type(counting_jt9_decoder) :: my_jt9
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |   type(counting_ft8_decoder) :: my_ft8
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-05-19 20:41:27 +00:00
										 |  |  |   !cast C character arrays to Fortran character strings
 | 
					
						
							|  |  |  |   datetime=transfer(params%datetime, datetime)
 | 
					
						
							|  |  |  |   mycall=transfer(params%mycall,mycall)
 | 
					
						
							|  |  |  |   hiscall=transfer(params%hiscall,hiscall)
 | 
					
						
							|  |  |  |   mygrid=transfer(params%mygrid,mygrid)
 | 
					
						
							|  |  |  |   hisgrid=transfer(params%hisgrid,hisgrid)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-06-09 23:39:19 +00:00
										 |  |  |   ! initialize decode counts
 | 
					
						
							|  |  |  |   my_jt4%decoded = 0
 | 
					
						
							|  |  |  |   my_jt65%decoded = 0
 | 
					
						
							|  |  |  |   my_jt9%decoded = 0
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |   my_ft8%decoded = 0
 | 
					
						
							| 
									
										
										
										
											2016-06-09 23:39:19 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-05 18:53:00 +00:00
										 |  |  |   single_decode=iand(params%nexp_decode,32).ne.0
 | 
					
						
							| 
									
										
										
										
											2016-10-24 15:25:25 +00:00
										 |  |  |   bVHF=iand(params%nexp_decode,64).ne.0
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   if(mod(params%nranera,2).eq.0) ntrials=10**(params%nranera/2)
 | 
					
						
							|  |  |  |   if(mod(params%nranera,2).eq.1) ntrials=3*10**(params%nranera/2)
 | 
					
						
							|  |  |  |   if(params%nranera.eq.0) ntrials=0
 | 
					
						
							| 
									
										
										
										
											2017-06-29 13:42:24 +00:00
										 |  |  |   
 | 
					
						
							|  |  |  |   nfail=0
 | 
					
						
							|  |  |  | 10 if (params%nagain) then
 | 
					
						
							|  |  |  |      open(13,file=trim(temp_dir)//'/decoded.txt',status='unknown',            &
 | 
					
						
							|  |  |  |           position='append',iostat=ios)
 | 
					
						
							|  |  |  |   else
 | 
					
						
							| 
									
										
										
										
											2017-10-30 20:47:08 +00:00
										 |  |  |      open(13,file=trim(temp_dir)//'/decoded.txt',status='unknown',iostat=ios)
 | 
					
						
							| 
									
										
										
										
											2018-05-01 17:14:21 +00:00
										 |  |  |   endif
 | 
					
						
							|  |  |  |   if(params%nmode.eq.8) then
 | 
					
						
							|  |  |  |      inquire(file=trim(temp_dir)//'/houndcallers.txt',exist=ex)
 | 
					
						
							|  |  |  |      if(.not.ex) then
 | 
					
						
							|  |  |  |         c2fox='            '
 | 
					
						
							|  |  |  |         g2fox='    '
 | 
					
						
							|  |  |  |         nsnrfox=-99
 | 
					
						
							|  |  |  |         nfreqfox=-99
 | 
					
						
							|  |  |  |         n30z=0
 | 
					
						
							|  |  |  |         nwrap=0
 | 
					
						
							|  |  |  |         nfox=0
 | 
					
						
							| 
									
										
										
										
											2018-04-24 14:15:13 +00:00
										 |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2018-05-01 17:14:21 +00:00
										 |  |  |      open(19,file=trim(temp_dir)//'/houndcallers.txt',status='unknown')
 | 
					
						
							| 
									
										
										
										
											2017-10-30 20:47:08 +00:00
										 |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2018-05-01 17:14:21 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-06-29 13:42:24 +00:00
										 |  |  |   if(ios.ne.0) then
 | 
					
						
							|  |  |  |      nfail=nfail+1
 | 
					
						
							|  |  |  |      if(nfail.le.3) then
 | 
					
						
							| 
									
										
										
										
											2017-07-20 15:15:00 +00:00
										 |  |  |         call sleep_msec(10)
 | 
					
						
							| 
									
										
										
										
											2017-06-29 13:42:24 +00:00
										 |  |  |         go to 10
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2015-11-18 01:28:12 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |   if(params%nmode.eq.8) then
 | 
					
						
							|  |  |  | ! We're in FT8 mode
 | 
					
						
							|  |  |  |      call timer('decft8  ',0)
 | 
					
						
							| 
									
										
										
										
											2017-07-03 19:52:36 +00:00
										 |  |  |      newdat=params%newdat
 | 
					
						
							| 
									
										
										
										
											2018-07-27 09:30:00 -04:00
										 |  |  |      ncontest=iand(params%nexp_decode,7)
 | 
					
						
							| 
									
										
										
										
											2017-07-28 15:50:13 +00:00
										 |  |  |      call my_ft8%decode(ft8_decoded,id2,params%nQSOProgress,params%nfqso,    &
 | 
					
						
							|  |  |  |           params%nftx,newdat,params%nutc,params%nfa,params%nfb,              &
 | 
					
						
							| 
									
										
										
										
											2018-07-27 09:30:00 -04:00
										 |  |  |           params%ndepth,ncontest,logical(params%nagain),                     &
 | 
					
						
							| 
									
										
										
										
											2018-07-05 07:51:10 -05:00
										 |  |  |           logical(params%lft8apon),logical(params%lapcqonly),                &
 | 
					
						
							| 
									
										
										
										
											2018-07-25 15:19:57 -04:00
										 |  |  |           logical(params%ldecode77),params%napwid,                           &
 | 
					
						
							|  |  |  |           mycall,hiscall,hisgrid)
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |      call timer('decft8  ',1)
 | 
					
						
							| 
									
										
										
										
											2017-12-16 20:56:42 +00:00
										 |  |  |      if(nfox.gt.0) then
 | 
					
						
							| 
									
										
										
										
											2017-12-19 17:01:38 +00:00
										 |  |  |         n30min=minval(n30fox(1:nfox))
 | 
					
						
							|  |  |  |         n30max=maxval(n30fox(1:nfox))
 | 
					
						
							| 
									
										
										
										
											2017-12-16 20:56:42 +00:00
										 |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2017-11-01 14:32:21 +00:00
										 |  |  |      j=0
 | 
					
						
							|  |  |  |      rewind 19
 | 
					
						
							| 
									
										
										
										
											2017-11-14 21:01:20 +00:00
										 |  |  |      if(nfox.eq.0) then
 | 
					
						
							|  |  |  |         endfile 19
 | 
					
						
							|  |  |  |         rewind 19
 | 
					
						
							|  |  |  |      else
 | 
					
						
							|  |  |  |         do i=1,nfox
 | 
					
						
							| 
									
										
										
										
											2017-12-19 17:01:38 +00:00
										 |  |  |            n=n30fox(i)
 | 
					
						
							|  |  |  |            if(n30max-n30fox(i).le.4) then
 | 
					
						
							| 
									
										
										
										
											2017-11-14 21:01:20 +00:00
										 |  |  |               j=j+1
 | 
					
						
							|  |  |  |               c2fox(j)=c2fox(i)
 | 
					
						
							|  |  |  |               g2fox(j)=g2fox(i)
 | 
					
						
							|  |  |  |               nsnrfox(j)=nsnrfox(i)
 | 
					
						
							|  |  |  |               nfreqfox(j)=nfreqfox(i)
 | 
					
						
							| 
									
										
										
										
											2017-12-19 17:01:38 +00:00
										 |  |  |               n30fox(j)=n
 | 
					
						
							|  |  |  |               m=n30max-n
 | 
					
						
							| 
									
										
										
										
											2018-03-16 18:56:29 +00:00
										 |  |  |               if(len(trim(g2fox(j))).eq.4) then
 | 
					
						
							| 
									
										
										
										
											2018-05-19 20:41:27 +00:00
										 |  |  |                  call azdist(mygrid,g2fox(j),0.d0,nAz,nEl,nDmiles,nDkm, &
 | 
					
						
							| 
									
										
										
										
											2018-03-16 18:56:29 +00:00
										 |  |  |                       nHotAz,nHotABetter)
 | 
					
						
							|  |  |  |               else
 | 
					
						
							|  |  |  |                  nDkm=9999
 | 
					
						
							|  |  |  |               endif
 | 
					
						
							| 
									
										
										
										
											2017-11-27 20:22:44 +00:00
										 |  |  |               write(19,1004) c2fox(j),g2fox(j),nsnrfox(j),nfreqfox(j),nDkm,m
 | 
					
						
							|  |  |  | 1004          format(a12,1x,a4,i5,i6,i7,i3)
 | 
					
						
							| 
									
										
										
										
											2017-11-14 21:01:20 +00:00
										 |  |  |            endif
 | 
					
						
							|  |  |  |         enddo
 | 
					
						
							|  |  |  |         nfox=j
 | 
					
						
							|  |  |  |         flush(19)
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |      go to 800
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2017-06-29 13:42:24 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-04-18 14:15:09 +00:00
										 |  |  |   rms=sqrt(dot_product(float(id2(300000:310000)),            &
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |        float(id2(300000:310000)))/10000.0)
 | 
					
						
							| 
									
										
										
										
											2016-12-22 20:51:27 +00:00
										 |  |  |   if(rms.lt.2.0) go to 800
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | ! Zap data at start that might come from T/R switching transient?
 | 
					
						
							|  |  |  |   nadd=100
 | 
					
						
							|  |  |  |   k=0
 | 
					
						
							|  |  |  |   bad0=.false.
 | 
					
						
							|  |  |  |   do i=1,240
 | 
					
						
							|  |  |  |      sq=0.
 | 
					
						
							|  |  |  |      do n=1,nadd
 | 
					
						
							|  |  |  |         k=k+1
 | 
					
						
							|  |  |  |         sq=sq + float(id2(k))**2
 | 
					
						
							|  |  |  |      enddo
 | 
					
						
							|  |  |  |      rms=sqrt(sq/nadd)
 | 
					
						
							|  |  |  |      if(rms.gt.10000.0) then
 | 
					
						
							|  |  |  |         bad0=.true.
 | 
					
						
							|  |  |  |         kbad=k
 | 
					
						
							|  |  |  |         rmsbad=rms
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							|  |  |  |   enddo
 | 
					
						
							|  |  |  |   if(bad0) then
 | 
					
						
							|  |  |  |      nz=min(NTMAX*12000,kbad+100)
 | 
					
						
							| 
									
										
										
										
											2017-01-27 02:22:54 +00:00
										 |  |  | !     id2(1:nz)=0                ! temporarily disabled as it can breaak the JT9 decoder, maybe others
 | 
					
						
							| 
									
										
										
										
											2016-12-22 20:51:27 +00:00
										 |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2017-02-07 14:31:11 +00:00
										 |  |  |   
 | 
					
						
							| 
									
										
										
										
											2016-07-06 14:18:23 +00:00
										 |  |  |   if(params%nmode.eq.4 .or. params%nmode.eq.65) open(14,file=trim(temp_dir)// &
 | 
					
						
							|  |  |  |        '/avemsg.txt',status='unknown')
 | 
					
						
							|  |  |  |   if(params%nmode.eq.164) open(17,file=trim(temp_dir)//'/red.dat',          &
 | 
					
						
							| 
									
										
										
										
											2017-02-10 16:38:19 +00:00
										 |  |  |        status='unknown')
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   if(params%nmode.eq.4) then
 | 
					
						
							| 
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 |  |  |      jz=52*nfsample
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |      if(params%newdat) then
 | 
					
						
							| 
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 |  |  |         if(nfsample.eq.12000) call wav11(id2,jz,dd)
 | 
					
						
							|  |  |  |         if(nfsample.eq.11025) dd(1:jz)=id2(1:jz)
 | 
					
						
							|  |  |  |      endif
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |      call my_jt4%decode(jt4_decoded,dd,jz,params%nutc,params%nfqso,         &
 | 
					
						
							|  |  |  |           params%ntol,params%emedelay,params%dttol,logical(params%nagain),  &
 | 
					
						
							|  |  |  |           params%ndepth,logical(params%nclearave),params%minsync,           &
 | 
					
						
							| 
									
										
										
										
											2018-05-19 20:41:27 +00:00
										 |  |  |           params%minw,params%nsubmode,mycall,hiscall,         &
 | 
					
						
							|  |  |  |           hisgrid,params%nlist,params%listutc,jt4_average)
 | 
					
						
							| 
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 |  |  |      go to 800
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  |   npts65=52*12000
 | 
					
						
							| 
									
										
										
										
											2016-12-20 21:27:23 +00:00
										 |  |  |   if(params%nmode.eq.164) npts65=54*12000
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  |   if(baddata(id2,npts65)) then
 | 
					
						
							|  |  |  |      nsynced=0
 | 
					
						
							|  |  |  |      ndecoded=0
 | 
					
						
							|  |  |  |      go to 800
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							| 
									
										
										
										
											2016-01-01 15:35:00 +00:00
										 |  |  |  
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   ntol65=params%ntol              !### is this OK? ###
 | 
					
						
							|  |  |  |   newdat65=params%newdat
 | 
					
						
							|  |  |  |   newdat9=params%newdat
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | !$call omp_set_dynamic(.true.)
 | 
					
						
							|  |  |  | !$omp parallel sections num_threads(2) copyin(/timer_private/) shared(ndecoded) if(.true.) !iif() needed on Mac
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | !$omp section
 | 
					
						
							| 
									
										
										
										
											2016-07-06 14:18:23 +00:00
										 |  |  |   if(params%nmode.eq.65 .or. params%nmode.eq.164 .or.                      &
 | 
					
						
							| 
									
										
										
										
											2016-06-24 14:36:03 +00:00
										 |  |  |        (params%nmode.eq.(65+9) .and. params%ntxmode.eq.65)) then
 | 
					
						
							| 
									
										
										
										
											2016-12-22 20:51:27 +00:00
										 |  |  | ! We're in JT65 or QRA64 mode, or should do JT65 first
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |      if(newdat65) dd(1:npts65)=id2(1:npts65)
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |      nf1=params%nfa
 | 
					
						
							|  |  |  |      nf2=params%nfb
 | 
					
						
							| 
									
										
										
										
											2015-02-01 20:11:10 +00:00
										 |  |  |      call timer('jt65a   ',0)
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  |      call my_jt65%decode(jt65_decoded,dd,npts65,newdat65,params%nutc,      &
 | 
					
						
							|  |  |  |           nf1,nf2,params%nfqso,ntol65,params%nsubmode,params%minsync,      &
 | 
					
						
							|  |  |  |           logical(params%nagain),params%n2pass,logical(params%nrobust),    &
 | 
					
						
							| 
									
										
										
										
											2016-12-22 20:51:27 +00:00
										 |  |  |           ntrials,params%naggressive,params%ndepth,params%emedelay,        &
 | 
					
						
							| 
									
										
										
										
											2018-05-19 20:41:27 +00:00
										 |  |  |           logical(params%nclearave),mycall,hiscall,          &
 | 
					
						
							|  |  |  |           hisgrid,params%nexp_decode,params%nQSOProgress,           &
 | 
					
						
							| 
									
										
										
										
											2017-11-04 17:03:56 +00:00
										 |  |  |           logical(params%ljt65apon))
 | 
					
						
							| 
									
										
										
										
											2015-02-01 20:11:10 +00:00
										 |  |  |      call timer('jt65a   ',1)
 | 
					
						
							| 
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   else if(params%nmode.eq.9 .or. (params%nmode.eq.(65+9) .and. params%ntxmode.eq.9)) then
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | ! We're in JT9 mode, or should do JT9 first
 | 
					
						
							| 
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 |  |  |      call timer('decjt9  ',0)
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |      call my_jt9%decode(jt9_decoded,ss,id2,params%nfqso,       &
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  |           newdat9,params%npts8,params%nfa,params%nfsplit,params%nfb,       &
 | 
					
						
							|  |  |  |           params%ntol,params%nzhsym,logical(params%nagain),params%ndepth,  &
 | 
					
						
							| 
									
										
										
										
											2016-04-05 14:17:34 +00:00
										 |  |  |           params%nmode,params%nsubmode,params%nexp_decode)
 | 
					
						
							| 
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 |  |  |      call timer('decjt9  ',1)
 | 
					
						
							|  |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | !$omp section
 | 
					
						
							|  |  |  |   if(params%nmode.eq.(65+9)) then       !Do the other mode (we're in dual mode)
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |      if (params%ntxmode.eq.9) then
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |         if(newdat65) dd(1:npts65)=id2(1:npts65)
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |         nf1=params%nfa
 | 
					
						
							|  |  |  |         nf2=params%nfb
 | 
					
						
							| 
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 |  |  |         call timer('jt65a   ',0)
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  |         call my_jt65%decode(jt65_decoded,dd,npts65,newdat65,params%nutc,   &
 | 
					
						
							|  |  |  |              nf1,nf2,params%nfqso,ntol65,params%nsubmode,params%minsync,   &
 | 
					
						
							|  |  |  |              logical(params%nagain),params%n2pass,logical(params%nrobust), &
 | 
					
						
							| 
									
										
										
										
											2016-12-22 20:51:27 +00:00
										 |  |  |              ntrials,params%naggressive,params%ndepth,params%emedelay,     &
 | 
					
						
							| 
									
										
										
										
											2018-05-19 20:41:27 +00:00
										 |  |  |              logical(params%nclearave),mycall,hiscall,       &
 | 
					
						
							|  |  |  |              hisgrid,params%nexp_decode,params%nQSOProgress,        &
 | 
					
						
							| 
									
										
										
										
											2017-11-04 17:03:56 +00:00
										 |  |  |              logical(params%ljt65apon))
 | 
					
						
							| 
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 |  |  |         call timer('jt65a   ',1)
 | 
					
						
							|  |  |  |      else
 | 
					
						
							|  |  |  |         call timer('decjt9  ',0)
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |         call my_jt9%decode(jt9_decoded,ss,id2,params%nfqso,                &
 | 
					
						
							| 
									
										
										
										
											2016-04-01 17:57:08 +00:00
										 |  |  |              newdat9,params%npts8,params%nfa,params%nfsplit,params%nfb,    &
 | 
					
						
							|  |  |  |              params%ntol,params%nzhsym,logical(params%nagain),             &
 | 
					
						
							| 
									
										
										
										
											2016-04-05 14:17:34 +00:00
										 |  |  |              params%ndepth,params%nmode,params%nsubmode,params%nexp_decode)
 | 
					
						
							| 
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 |  |  |         call timer('decjt9  ',1)
 | 
					
						
							|  |  |  |      end if
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  |   endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | !$omp end parallel sections
 | 
					
						
							| 
									
										
										
										
											2015-02-01 16:23:36 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  | ! JT65 is not yet producing info for nsynced, ndecoded.
 | 
					
						
							| 
									
										
										
										
											2017-06-27 20:50:17 +00:00
										 |  |  | 800 ndecoded = my_jt4%decoded + my_jt65%decoded + my_jt9%decoded + my_ft8%decoded
 | 
					
						
							|  |  |  |   write(*,1010) nsynced,ndecoded
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  | 1010 format('<DecodeFinished>',2i4)
 | 
					
						
							|  |  |  |   call flush(6)
 | 
					
						
							| 
									
										
										
										
											2017-12-16 20:56:42 +00:00
										 |  |  |   close(13)
 | 
					
						
							|  |  |  |   close(19)
 | 
					
						
							| 
									
										
										
										
											2015-12-17 20:29:55 +00:00
										 |  |  |   if(params%nmode.eq.4 .or. params%nmode.eq.65) close(14)
 | 
					
						
							| 
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |   return
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | contains
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |   subroutine jt4_decoded(this,snr,dt,freq,have_sync,sync,is_deep,    &
 | 
					
						
							| 
									
										
										
										
											2016-05-19 16:13:51 +00:00
										 |  |  |        decoded0,qual,ich,is_average,ave)
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     implicit none
 | 
					
						
							|  |  |  |     class(jt4_decoder), intent(inout) :: this
 | 
					
						
							|  |  |  |     integer, intent(in) :: snr
 | 
					
						
							|  |  |  |     real, intent(in) :: dt
 | 
					
						
							|  |  |  |     integer, intent(in) :: freq
 | 
					
						
							|  |  |  |     logical, intent(in) :: have_sync
 | 
					
						
							|  |  |  |     logical, intent(in) :: is_deep
 | 
					
						
							|  |  |  |     character(len=1), intent(in) :: sync
 | 
					
						
							| 
									
										
										
										
											2016-05-19 16:13:51 +00:00
										 |  |  |     character(len=22), intent(in) :: decoded0
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     real, intent(in) :: qual
 | 
					
						
							|  |  |  |     integer, intent(in) :: ich
 | 
					
						
							|  |  |  |     logical, intent(in) :: is_average
 | 
					
						
							|  |  |  |     integer, intent(in) :: ave
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-19 16:13:51 +00:00
										 |  |  |     character*22 decoded
 | 
					
						
							|  |  |  |     character*3 cflags
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-06-09 19:39:48 +00:00
										 |  |  |     if(ich.eq.-99) stop                         !Silence compiler warning
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     if (have_sync) then
 | 
					
						
							| 
									
										
										
										
											2016-05-19 16:13:51 +00:00
										 |  |  |        decoded=decoded0
 | 
					
						
							| 
									
										
										
										
											2016-05-19 19:19:47 +00:00
										 |  |  |        cflags='   '
 | 
					
						
							|  |  |  |        if(decoded.ne.'                      ') cflags='f  '
 | 
					
						
							| 
									
										
										
										
											2016-05-19 16:13:51 +00:00
										 |  |  |        if(is_deep) then
 | 
					
						
							|  |  |  |           cflags(1:2)='d1'
 | 
					
						
							|  |  |  |           write(cflags(3:3),'(i1)') min(int(qual),9)
 | 
					
						
							|  |  |  |           if(qual.ge.10.0) cflags(3:3)='*'
 | 
					
						
							|  |  |  |           if(qual.lt.3.0) decoded(22:22)='?'
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							|  |  |  |        if(is_average) then
 | 
					
						
							|  |  |  |           write(cflags(2:2),'(i1)') min(ave,9)
 | 
					
						
							|  |  |  |           if(ave.ge.10) cflags(2:2)='*'
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							|  |  |  |        write(*,1000) params%nutc,snr,dt,freq,sync,decoded,cflags
 | 
					
						
							|  |  |  | 1000   format(i4.4,i4,f5.1,i5,1x,'$',a1,1x,a22,1x,a3)
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     else
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |        write(*,1000) params%nutc,snr,dt,freq
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     end if
 | 
					
						
							| 
									
										
										
										
											2016-05-17 18:34:57 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     select type(this)
 | 
					
						
							|  |  |  |     type is (counting_jt4_decoder)
 | 
					
						
							|  |  |  |        this%decoded = this%decoded + 1
 | 
					
						
							|  |  |  |     end select
 | 
					
						
							|  |  |  |   end subroutine jt4_decoded
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   subroutine jt4_average (this, used, utc, sync, dt, freq, flip)
 | 
					
						
							|  |  |  |     implicit none
 | 
					
						
							|  |  |  |     class(jt4_decoder), intent(inout) :: this
 | 
					
						
							|  |  |  |     logical, intent(in) :: used
 | 
					
						
							|  |  |  |     integer, intent(in) :: utc
 | 
					
						
							|  |  |  |     real, intent(in) :: sync
 | 
					
						
							|  |  |  |     real, intent(in) :: dt
 | 
					
						
							|  |  |  |     integer, intent(in) :: freq
 | 
					
						
							|  |  |  |     logical, intent(in) :: flip
 | 
					
						
							| 
									
										
										
										
											2015-12-30 14:57:50 +00:00
										 |  |  |     character(len=1) :: cused, csync
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-30 14:57:50 +00:00
										 |  |  |     cused = '.'
 | 
					
						
							|  |  |  |     csync = '*'
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     if (used) cused = '$'
 | 
					
						
							|  |  |  |     if (flip) csync = '$'
 | 
					
						
							|  |  |  |     write(14,1000) cused,utc,sync,dt,freq,csync
 | 
					
						
							|  |  |  | 1000 format(a1,i5.4,f6.1,f6.2,i6,1x,a1)
 | 
					
						
							|  |  |  |   end subroutine jt4_average
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |   subroutine jt65_decoded(this,sync,snr,dt,freq,drift,nflip,width,     &
 | 
					
						
							|  |  |  |        decoded0,ft,qual,nsmo,nsum,minsync)
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     use jt65_decode
 | 
					
						
							|  |  |  |     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-03-22 14:12:59 +00:00
										 |  |  |     character(len=22), intent(in) :: decoded0
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     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
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-11-05 14:44:15 +00:00
										 |  |  |     integer i,nap,nft
 | 
					
						
							| 
									
										
										
										
											2016-06-09 19:39:48 +00:00
										 |  |  |     logical is_deep,is_average
 | 
					
						
							| 
									
										
										
										
											2016-05-19 16:13:51 +00:00
										 |  |  |     character decoded*22,csync*2,cflags*3
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-06-09 19:39:48 +00:00
										 |  |  |     if(width.eq.-9999.0) stop              !Silence compiler warning
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  | !$omp critical(decode_results)
 | 
					
						
							| 
									
										
										
										
											2016-03-22 14:12:59 +00:00
										 |  |  |     decoded=decoded0
 | 
					
						
							| 
									
										
										
										
											2016-05-24 16:00:00 +00:00
										 |  |  |     cflags='   '
 | 
					
						
							|  |  |  |     is_deep=ft.eq.2
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-11-21 16:51:11 +00:00
										 |  |  |     if(ft.ge.80) then                      !QRA64 mode
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  |        nft=ft-100
 | 
					
						
							| 
									
										
										
										
											2016-07-01 15:25:41 +00:00
										 |  |  |        csync=': '
 | 
					
						
							| 
									
										
										
										
											2016-12-08 15:38:54 +00:00
										 |  |  |        if(sync-3.4.ge.float(minsync) .or. nft.ge.0) csync=':*'
 | 
					
						
							| 
									
										
										
										
											2016-07-01 15:25:41 +00:00
										 |  |  |        if(nft.lt.0) then
 | 
					
						
							| 
									
										
										
										
											2016-07-01 15:16:00 +00:00
										 |  |  |           write(*,1009) params%nutc,snr,dt,freq,csync,decoded
 | 
					
						
							|  |  |  |        else
 | 
					
						
							| 
									
										
										
										
											2016-11-28 15:11:00 +00:00
										 |  |  |           write(*,1009) params%nutc,snr,dt,freq,csync,decoded,nft
 | 
					
						
							|  |  |  | 1009      format(i4.4,i4,f5.1,i5,1x,a2,1x,a22,i2)
 | 
					
						
							| 
									
										
										
										
											2016-07-01 15:16:00 +00:00
										 |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  |        write(13,1011) params%nutc,nint(sync),snr,dt,float(freq),drift,    &
 | 
					
						
							| 
									
										
										
										
											2016-11-28 15:11:00 +00:00
										 |  |  |             decoded,nft
 | 
					
						
							| 
									
										
										
										
											2016-07-02 12:48:27 +00:00
										 |  |  | 1011   format(i4.4,i4,i5,f6.2,f8.0,i4,3x,a22,' QRA64',i3)
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  |        go to 100
 | 
					
						
							|  |  |  |     endif
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  |     
 | 
					
						
							| 
									
										
										
										
											2016-03-23 15:08:00 +00:00
										 |  |  |     if(ft.eq.0 .and. minsync.ge.0 .and. int(sync).lt.minsync) then
 | 
					
						
							| 
									
										
										
										
											2016-05-05 18:53:00 +00:00
										 |  |  |        write(*,1010) params%nutc,snr,dt,freq
 | 
					
						
							| 
									
										
										
										
											2016-03-07 20:00:23 +00:00
										 |  |  |     else
 | 
					
						
							| 
									
										
										
										
											2016-05-19 16:13:51 +00:00
										 |  |  |        is_average=nsum.ge.2
 | 
					
						
							| 
									
										
										
										
											2016-10-24 15:25:25 +00:00
										 |  |  |        if(bVHF .and. ft.gt.0) then
 | 
					
						
							| 
									
										
										
										
											2016-05-19 16:13:51 +00:00
										 |  |  |           cflags='f  '
 | 
					
						
							|  |  |  |           if(is_deep) then
 | 
					
						
							|  |  |  |              cflags(1:2)='d1'
 | 
					
						
							|  |  |  |              write(cflags(3:3),'(i1)') min(qual,9)
 | 
					
						
							|  |  |  |              if(qual.ge.10) cflags(3:3)='*'
 | 
					
						
							|  |  |  |              if(qual.lt.3) decoded(22:22)='?'
 | 
					
						
							|  |  |  |           endif
 | 
					
						
							|  |  |  |           if(is_average) then
 | 
					
						
							|  |  |  |              write(cflags(2:2),'(i1)') min(nsum,9)
 | 
					
						
							|  |  |  |              if(nsum.ge.10) cflags(2:2)='*'
 | 
					
						
							| 
									
										
										
										
											2016-03-22 14:12:59 +00:00
										 |  |  |           endif
 | 
					
						
							| 
									
										
										
										
											2017-11-05 14:44:15 +00:00
										 |  |  |           nap=ishft(ft,-2)
 | 
					
						
							|  |  |  |           if(nap.ne.0) then
 | 
					
						
							| 
									
										
										
										
											2017-12-02 16:04:51 +00:00
										 |  |  |             write(cflags(1:3),'(a1,i1)') 'a',nap 
 | 
					
						
							| 
									
										
										
										
											2017-11-05 14:44:15 +00:00
										 |  |  |           endif
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2016-05-04 18:16:09 +00:00
										 |  |  |        csync='# '
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |        i=0
 | 
					
						
							| 
									
										
										
										
											2016-10-24 20:48:24 +00:00
										 |  |  |        if(bVHF .and. nflip.ne.0 .and.                         &
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |             sync.ge.max(0.0,float(minsync))) then
 | 
					
						
							| 
									
										
										
										
											2016-05-04 18:16:09 +00:00
										 |  |  |           csync='#*'
 | 
					
						
							| 
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 |  |  |           if(nflip.eq.-1) then
 | 
					
						
							| 
									
										
										
										
											2016-05-04 18:16:09 +00:00
										 |  |  |              csync='##'
 | 
					
						
							| 
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 |  |  |              if(decoded.ne.'                      ') then
 | 
					
						
							|  |  |  |                 do i=22,1,-1
 | 
					
						
							|  |  |  |                    if(decoded(i:i).ne.' ') exit
 | 
					
						
							|  |  |  |                 enddo
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |                 if(i.gt.18) i=18
 | 
					
						
							| 
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 |  |  |                 decoded(i+2:i+4)='OOO'
 | 
					
						
							|  |  |  |              endif
 | 
					
						
							|  |  |  |           endif
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  |        write(*,1010) params%nutc,snr,dt,freq,csync,decoded,cflags
 | 
					
						
							|  |  |  | 1010   format(i4.4,i4,f5.1,i5,1x,a2,1x,a22,1x,a3)
 | 
					
						
							| 
									
										
										
										
											2016-03-07 20:00:23 +00:00
										 |  |  |     endif
 | 
					
						
							| 
									
										
										
										
											2016-05-17 17:19:27 +00:00
										 |  |  |     write(13,1012) params%nutc,nint(sync),snr,dt,float(freq),drift,    &
 | 
					
						
							|  |  |  |          decoded,ft,nsum,nsmo
 | 
					
						
							| 
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 |  |  | 1012 format(i4.4,i4,i5,f6.2,f8.0,i4,3x,a22,' JT65',3i3)
 | 
					
						
							| 
									
										
										
										
											2016-06-30 20:38:36 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | 100 call flush(6)
 | 
					
						
							| 
									
										
										
										
											2015-12-31 01:30:31 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 |  |  | !$omp end critical(decode_results)
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     select type(this)
 | 
					
						
							|  |  |  |     type is (counting_jt65_decoder)
 | 
					
						
							|  |  |  |        this%decoded = this%decoded + 1
 | 
					
						
							|  |  |  |     end select
 | 
					
						
							|  |  |  |   end subroutine jt65_decoded
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |   subroutine jt9_decoded (this, sync, snr, dt, freq, drift, decoded)
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  |     use jt9_decode
 | 
					
						
							|  |  |  |     implicit none
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     class(jt9_decoder), intent(inout) :: this
 | 
					
						
							|  |  |  |     real, intent(in) :: sync
 | 
					
						
							|  |  |  |     integer, intent(in) :: snr
 | 
					
						
							|  |  |  |     real, intent(in) :: dt
 | 
					
						
							|  |  |  |     real, intent(in) :: freq
 | 
					
						
							|  |  |  |     integer, intent(in) :: drift
 | 
					
						
							|  |  |  |     character(len=22), intent(in) :: decoded
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     !$omp critical(decode_results)
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |     write(*,1000) params%nutc,snr,dt,nint(freq),decoded
 | 
					
						
							| 
									
										
										
										
											2016-05-05 18:53:00 +00:00
										 |  |  | 1000 format(i4.4,i4,f5.1,i5,1x,'@ ',1x,a22)
 | 
					
						
							| 
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 |  |  |     write(13,1002) params%nutc,nint(sync),snr,dt,freq,drift,decoded
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  | 1002 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a22,' JT9')
 | 
					
						
							|  |  |  |     call flush(6)
 | 
					
						
							|  |  |  |     !$omp end critical(decode_results)
 | 
					
						
							|  |  |  |     select type(this)
 | 
					
						
							|  |  |  |     type is (counting_jt9_decoder)
 | 
					
						
							|  |  |  |        this%decoded = this%decoded + 1
 | 
					
						
							|  |  |  |     end select
 | 
					
						
							|  |  |  |   end subroutine jt9_decoded
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-07-22 17:12:48 +00:00
										 |  |  |   subroutine ft8_decoded (this,sync,snr,dt,freq,decoded,nap,qual)
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |     use ft8_decode
 | 
					
						
							|  |  |  |     implicit none
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     class(ft8_decoder), intent(inout) :: this
 | 
					
						
							|  |  |  |     real, intent(in) :: sync
 | 
					
						
							|  |  |  |     integer, intent(in) :: snr
 | 
					
						
							|  |  |  |     real, intent(in) :: dt
 | 
					
						
							|  |  |  |     real, intent(in) :: freq
 | 
					
						
							| 
									
										
										
										
											2017-12-19 20:01:06 +00:00
										 |  |  |     character(len=37), intent(in) :: decoded
 | 
					
						
							| 
									
										
										
										
											2018-05-09 14:22:19 +00:00
										 |  |  |     character c1*12,c2*12,g2*4,w*4,ctmp*12
 | 
					
						
							| 
									
										
										
										
											2018-03-16 18:56:29 +00:00
										 |  |  |     integer i0,i1,i2,i3,i4,i5,i6,n30,nwrap
 | 
					
						
							| 
									
										
										
										
											2017-07-22 17:12:48 +00:00
										 |  |  |     integer, intent(in) :: nap 
 | 
					
						
							|  |  |  |     real, intent(in) :: qual 
 | 
					
						
							| 
									
										
										
										
											2017-07-25 19:06:05 +00:00
										 |  |  |     character*2 annot
 | 
					
						
							| 
									
										
										
										
											2017-12-19 20:01:06 +00:00
										 |  |  |     character*37 decoded0
 | 
					
						
							| 
									
										
										
										
											2017-12-19 15:18:56 +00:00
										 |  |  |     logical isgrid4,first,b0,b1,b2
 | 
					
						
							| 
									
										
										
										
											2017-10-30 20:47:08 +00:00
										 |  |  |     data first/.true./
 | 
					
						
							|  |  |  |     save
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     isgrid4(w)=(len_trim(w).eq.4 .and.                                        &
 | 
					
						
							|  |  |  |          ichar(w(1:1)).ge.ichar('A') .and. ichar(w(1:1)).le.ichar('R') .and.  &
 | 
					
						
							|  |  |  |          ichar(w(2:2)).ge.ichar('A') .and. ichar(w(2:2)).le.ichar('R') .and.  &
 | 
					
						
							|  |  |  |          ichar(w(3:3)).ge.ichar('0') .and. ichar(w(3:3)).le.ichar('9') .and.  &
 | 
					
						
							|  |  |  |          ichar(w(4:4)).ge.ichar('0') .and. ichar(w(4:4)).le.ichar('9'))
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |     if(first) then
 | 
					
						
							|  |  |  |        c2fox='            '
 | 
					
						
							|  |  |  |        g2fox='    '
 | 
					
						
							|  |  |  |        nsnrfox=-99
 | 
					
						
							|  |  |  |        nfreqfox=-99
 | 
					
						
							| 
									
										
										
										
											2017-12-19 17:01:38 +00:00
										 |  |  |        n30z=0
 | 
					
						
							| 
									
										
										
										
											2017-11-27 20:22:44 +00:00
										 |  |  |        nwrap=0
 | 
					
						
							| 
									
										
										
										
											2017-10-30 20:47:08 +00:00
										 |  |  |        nfox=0
 | 
					
						
							|  |  |  |        first=.false.
 | 
					
						
							|  |  |  |     endif
 | 
					
						
							|  |  |  |     
 | 
					
						
							| 
									
										
										
										
											2017-12-08 17:03:11 +00:00
										 |  |  |     decoded0=decoded
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-07-25 19:06:05 +00:00
										 |  |  |     annot='  ' 
 | 
					
						
							| 
									
										
										
										
											2017-07-22 17:12:48 +00:00
										 |  |  |     if(nap.ne.0) then
 | 
					
						
							| 
									
										
										
										
											2017-12-08 17:03:11 +00:00
										 |  |  |        write(annot,'(a1,i1)') 'a',nap
 | 
					
						
							| 
									
										
										
										
											2018-07-28 17:32:45 -05:00
										 |  |  |        if(qual.lt.0.17) decoded0(37:37)='?'
 | 
					
						
							| 
									
										
										
										
											2017-07-22 17:12:48 +00:00
										 |  |  |     endif
 | 
					
						
							| 
									
										
										
										
											2017-12-08 17:03:11 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-04 10:15:01 -05:00
										 |  |  | !    i0=index(decoded0,';')
 | 
					
						
							|  |  |  | ! Always print 37 characters? Or, send i3,n3 up to here from ft8b_2 and use them
 | 
					
						
							|  |  |  | ! to decide how many chars to print?
 | 
					
						
							|  |  |  | !TEMP
 | 
					
						
							|  |  |  |     i0=1
 | 
					
						
							| 
									
										
										
										
											2017-12-08 17:03:11 +00:00
										 |  |  |     if(i0.le.0) write(*,1000) params%nutc,snr,dt,nint(freq),decoded0(1:22),annot
 | 
					
						
							| 
									
										
										
										
											2017-07-25 19:06:05 +00:00
										 |  |  | 1000 format(i6.6,i4,f5.1,i5,' ~ ',1x,a22,1x,a2)
 | 
					
						
							| 
									
										
										
										
											2018-07-28 17:32:45 -05:00
										 |  |  |     if(i0.gt.0) write(*,1001) params%nutc,snr,dt,nint(freq),decoded0,annot
 | 
					
						
							|  |  |  | 1001 format(i6.6,i4,f5.1,i5,' ~ ',1x,a37,1x,a2)
 | 
					
						
							| 
									
										
										
										
											2017-07-25 19:06:05 +00:00
										 |  |  |     write(13,1002) params%nutc,nint(sync),snr,dt,freq,0,decoded0
 | 
					
						
							| 
									
										
										
										
											2017-12-19 20:01:06 +00:00
										 |  |  | 1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a37,' FT8')
 | 
					
						
							| 
									
										
										
										
											2017-10-30 20:47:08 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |     i1=index(decoded0,' ')
 | 
					
						
							|  |  |  |     i2=i1 + index(decoded0(i1+1:),' ')
 | 
					
						
							|  |  |  |     i3=i2 + index(decoded0(i2+1:),' ')
 | 
					
						
							| 
									
										
										
										
											2017-11-14 21:01:20 +00:00
										 |  |  |     if(i1.ge.3 .and. i2.ge.7 .and. i3.ge.10) then
 | 
					
						
							|  |  |  |        c1=decoded0(1:i1-1)//'            '
 | 
					
						
							|  |  |  |        c2=decoded0(i1+1:i2-1)
 | 
					
						
							|  |  |  |        g2=decoded0(i2+1:i3-1)
 | 
					
						
							| 
									
										
										
										
											2018-05-19 20:41:27 +00:00
										 |  |  |        b0=c1.eq.mycall
 | 
					
						
							| 
									
										
										
										
											2018-05-09 14:22:19 +00:00
										 |  |  |        if(c1(1:3).eq.'DE ' .and. index(c2,'/').ge.2) b0=.true.
 | 
					
						
							| 
									
										
										
										
											2018-05-19 20:41:27 +00:00
										 |  |  |        if(len(trim(c1)).ne.len(trim(mycall))) then
 | 
					
						
							|  |  |  |           i4=index(trim(c1),trim(mycall))
 | 
					
						
							|  |  |  |           i5=index(trim(mycall),trim(c1))
 | 
					
						
							| 
									
										
										
										
											2017-12-19 15:18:56 +00:00
										 |  |  |           if(i4.ge.1 .or. i5.ge.1) b0=.true.
 | 
					
						
							|  |  |  |        endif
 | 
					
						
							|  |  |  |        b1=i3-i2.eq.5 .and. isgrid4(g2)
 | 
					
						
							|  |  |  |        b2=i3-i2.eq.1
 | 
					
						
							|  |  |  |        if(b0 .and. (b1.or.b2) .and. nint(freq).ge.1000) then
 | 
					
						
							| 
									
										
										
										
											2017-11-14 21:01:20 +00:00
										 |  |  |           n=params%nutc
 | 
					
						
							| 
									
										
										
										
											2017-12-19 17:01:38 +00:00
										 |  |  |           n30=(3600*(n/10000) + 60*mod((n/100),100) + mod(n,100))/30
 | 
					
						
							|  |  |  |           if(n30.lt.n30z) nwrap=nwrap+5760    !New UTC day, handle the wrap
 | 
					
						
							|  |  |  |           n30z=n30
 | 
					
						
							|  |  |  |           n30=n30+nwrap
 | 
					
						
							| 
									
										
										
										
											2017-11-14 21:01:20 +00:00
										 |  |  |           nfox=nfox+1
 | 
					
						
							|  |  |  |           c2fox(nfox)=c2
 | 
					
						
							|  |  |  |           g2fox(nfox)=g2
 | 
					
						
							|  |  |  |           nsnrfox(nfox)=snr
 | 
					
						
							|  |  |  |           nfreqfox(nfox)=nint(freq)
 | 
					
						
							| 
									
										
										
										
											2017-12-19 17:01:38 +00:00
										 |  |  |           n30fox(nfox)=n30
 | 
					
						
							| 
									
										
										
										
											2017-11-14 21:01:20 +00:00
										 |  |  |        endif
 | 
					
						
							| 
									
										
										
										
											2017-10-30 20:47:08 +00:00
										 |  |  |     endif
 | 
					
						
							|  |  |  |     
 | 
					
						
							| 
									
										
										
										
											2017-07-14 16:02:01 +00:00
										 |  |  |     call flush(6)
 | 
					
						
							|  |  |  |     call flush(13)
 | 
					
						
							| 
									
										
										
										
											2017-06-27 19:44:12 +00:00
										 |  |  |     
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |     select type(this)
 | 
					
						
							|  |  |  |     type is (counting_ft8_decoder)
 | 
					
						
							|  |  |  |        this%decoded = this%decoded + 1
 | 
					
						
							|  |  |  |     end select
 | 
					
						
							| 
									
										
										
										
											2017-06-27 19:44:12 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  |     return
 | 
					
						
							| 
									
										
										
										
											2017-06-17 15:55:30 +00:00
										 |  |  |   end subroutine ft8_decoded
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2015-12-29 23:52:55 +00:00
										 |  |  | end subroutine multimode_decoder
 |