| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  | subroutine ft4_decode(cdatetime0,tbuf,nfa,nfb,nQSOProgress,ncontest,nfqso, &
 | 
					
						
							| 
									
										
										
										
											2019-03-09 10:03:01 -06:00
										 |  |  |    iwave,ndecodes,mycall,hiscall,cqstr,line,data_dir)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  |    use packjt77
 | 
					
						
							|  |  |  |    include 'ft4_params.f90'
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |    parameter (NSS=NSPS/NDOWN)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-13 14:42:57 -05:00
										 |  |  |    character message*37,msgsent*37,msg0*37
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    character c77*77
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  |    character*61 line,linex(100)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    character*37 decodes(100)
 | 
					
						
							| 
									
										
										
										
											2019-02-01 11:56:08 -05:00
										 |  |  |    character*512 data_dir,fname
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    character*17 cdatetime0
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |    character*12 mycall,hiscall
 | 
					
						
							|  |  |  |    character*12 mycall0,hiscall0
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |    character*6 hhmmss
 | 
					
						
							| 
									
										
										
										
											2019-03-04 17:10:57 -06:00
										 |  |  |    character*4 cqstr,cqstr0
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |    complex cd2(0:NMAX/NDOWN-1)                  !Complex waveform
 | 
					
						
							|  |  |  |    complex cb(0:NMAX/NDOWN-1)
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:22:41 -05:00
										 |  |  |    complex cd(0:NN*NSS-1)                       !Complex waveform
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |    complex ctwk(4*NSS),ctwk2(4*NSS)
 | 
					
						
							|  |  |  |    complex csymb(NSS)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    complex cs(0:3,NN)
 | 
					
						
							|  |  |  |    real s4(0:3,NN)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |    real bmeta(2*NN),bmetb(2*NN),bmetc(2*NN)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    real a(5)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |    real llr(2*ND),llra(2*ND),llrb(2*ND),llrc(2*ND),llrd(2*ND)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    real s2(0:255)
 | 
					
						
							|  |  |  |    real candidate(3,100)
 | 
					
						
							|  |  |  |    real savg(NH1),sbase(NH1)
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |    integer apbits(2*ND)
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |    integer apmy_ru(28),aphis_fd(28)
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |    integer icos4a(0:3),icos4b(0:3),icos4c(0:3),icos4d(0:3)
 | 
					
						
							| 
									
										
										
										
											2019-03-13 10:31:23 -04:00
										 |  |  |    integer*2 iwave(NMAX)                 !Raw received data
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |    integer*1 message77(77),rvec(77),apmask(2*ND),cw(2*ND)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |    integer*1 hbits(2*NN)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    integer graymap(0:3)
 | 
					
						
							|  |  |  |    integer ip(1)
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |    integer nappasses(0:5)    ! # of decoding passes for QSO States 0-5
 | 
					
						
							|  |  |  |    integer naptypes(0:5,4)   ! nQSOProgress, decoding pass
 | 
					
						
							| 
									
										
										
										
											2019-03-04 17:10:57 -06:00
										 |  |  |    integer mcq(29)
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |    integer mrrr(19),m73(19),mrr73(19)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |    logical nohiscall,unpk77_success
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |    logical one(0:255,0:7)    ! 256 4-symbol sequences, 8 bits
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    logical first
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |    data icos4a/0,1,3,2/
 | 
					
						
							|  |  |  |    data icos4b/1,0,2,3/
 | 
					
						
							|  |  |  |    data icos4c/2,3,1,0/
 | 
					
						
							|  |  |  |    data icos4d/3,2,0,1/
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    data graymap/0,1,3,2/
 | 
					
						
							| 
									
										
										
										
											2019-02-13 14:42:57 -05:00
										 |  |  |    data msg0/' '/
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    data first/.true./
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |    data     mcq/0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,0,0/
 | 
					
						
							|  |  |  |    data    mrrr/0,1,1,1,1,1,1,0,1,0,0,1,0,0,1,0,0,0,1/
 | 
					
						
							|  |  |  |    data     m73/0,1,1,1,1,1,1,0,1,0,0,1,0,1,0,0,0,0,1/
 | 
					
						
							|  |  |  |    data   mrr73/0,1,1,1,1,1,1,0,0,1,1,1,0,1,0,1,0,0,1/
 | 
					
						
							|  |  |  |    data rvec/0,1,0,0,1,0,1,0,0,1,0,1,1,1,1,0,1,0,0,0,1,0,0,1,1,0,1,1,0, &
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |       1,0,0,1,0,1,1,0,0,0,0,1,0,0,0,1,0,1,0,0,1,1,1,1,0,0,1,0,1, &
 | 
					
						
							|  |  |  |       0,1,0,1,0,1,1,0,1,1,1,1,1,0,0,0,1,0,1/
 | 
					
						
							| 
									
										
										
										
											2019-03-09 10:03:01 -06:00
										 |  |  |    save fs,dt,tt,txt,twopi,h,one,first,linex,apbits,nappasses,naptypes, &
 | 
					
						
							| 
									
										
										
										
											2019-03-04 17:10:57 -06:00
										 |  |  |       mycall0,hiscall0,msg0,cqstr0
 | 
					
						
							| 
									
										
										
										
											2019-02-14 14:09:22 -05:00
										 |  |  |    
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |    call clockit('ft4_deco',0)
 | 
					
						
							| 
									
										
										
										
											2019-01-29 10:39:34 -05:00
										 |  |  |    hhmmss=cdatetime0(8:13)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  |    if(first) then
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |       fs=12000.0/NDOWN                !Sample rate after downsampling
 | 
					
						
							|  |  |  |       dt=1/fs                         !Sample interval after downsample (s)
 | 
					
						
							|  |  |  |       tt=NSPS*dt                      !Duration of "itone" symbols (s)
 | 
					
						
							|  |  |  |       txt=NZ*dt                       !Transmission length (s) without ramp up/down
 | 
					
						
							|  |  |  |       twopi=8.0*atan(1.0)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |       h=1.0
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |       one=.false.
 | 
					
						
							|  |  |  |       do i=0,255
 | 
					
						
							|  |  |  |          do j=0,7
 | 
					
						
							|  |  |  |             if(iand(i,2**j).ne.0) one(i,j)=.true.
 | 
					
						
							|  |  |  |          enddo
 | 
					
						
							|  |  |  |       enddo
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  |       mrrr=2*mod(mrrr+rvec(59:77),2)-1
 | 
					
						
							|  |  |  |       m73=2*mod(m73+rvec(59:77),2)-1
 | 
					
						
							|  |  |  |       mrr73=2*mod(mrr73+rvec(59:77),2)-1
 | 
					
						
							|  |  |  |       nappasses(0)=2
 | 
					
						
							|  |  |  |       nappasses(1)=2
 | 
					
						
							|  |  |  |       nappasses(2)=2
 | 
					
						
							|  |  |  |       nappasses(3)=2
 | 
					
						
							|  |  |  |       nappasses(4)=2
 | 
					
						
							|  |  |  |       nappasses(5)=3
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | ! iaptype
 | 
					
						
							|  |  |  | !------------------------
 | 
					
						
							| 
									
										
										
										
											2019-02-08 15:17:46 -06:00
										 |  |  | !   1        CQ     ???    ???           (29 ap bits)
 | 
					
						
							|  |  |  | !   2        MyCall ???    ???           (29 ap bits)
 | 
					
						
							|  |  |  | !   3        MyCall DxCall ???           (58 ap bits)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  | !   4        MyCall DxCall RRR           (77 ap bits)
 | 
					
						
							|  |  |  | !   5        MyCall DxCall 73            (77 ap bits)
 | 
					
						
							|  |  |  | !   6        MyCall DxCall RR73          (77 ap bits)
 | 
					
						
							| 
									
										
										
										
											2019-02-08 15:17:46 -06:00
										 |  |  | !********
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |       naptypes(0,1:4)=(/1,2,0,0/) ! Tx6 selected (CQ)
 | 
					
						
							|  |  |  |       naptypes(1,1:4)=(/2,3,0,0/) ! Tx1
 | 
					
						
							|  |  |  |       naptypes(2,1:4)=(/2,3,0,0/) ! Tx2
 | 
					
						
							|  |  |  |       naptypes(3,1:4)=(/3,6,0,0/) ! Tx3
 | 
					
						
							|  |  |  |       naptypes(4,1:4)=(/3,6,0,0/) ! Tx4
 | 
					
						
							|  |  |  |       naptypes(5,1:4)=(/3,1,2,0/) ! Tx5
 | 
					
						
							| 
									
										
										
										
											2019-02-08 16:44:18 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  |       mycall0=''
 | 
					
						
							|  |  |  |       hiscall0=''
 | 
					
						
							| 
									
										
										
										
											2019-03-04 17:10:57 -06:00
										 |  |  |       cqstr0=''
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |       first=.false.
 | 
					
						
							|  |  |  |    endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-03-04 17:10:57 -06:00
										 |  |  |    if(cqstr.ne.cqstr0) then
 | 
					
						
							|  |  |  |       i0=index(cqstr,' ')
 | 
					
						
							|  |  |  |       if(i0.le.1) then 
 | 
					
						
							|  |  |  |          message='CQ A1AA AA01'
 | 
					
						
							|  |  |  |       else
 | 
					
						
							|  |  |  |          message='CQ '//cqstr(1:i0-1)//' A1AA AA01'
 | 
					
						
							|  |  |  |       endif
 | 
					
						
							|  |  |  |       i3=-1
 | 
					
						
							|  |  |  |       n3=-1
 | 
					
						
							|  |  |  |       call pack77(message,i3,n3,c77)
 | 
					
						
							|  |  |  |       call unpack77(c77,1,msgsent,unpk77_success)
 | 
					
						
							|  |  |  |       read(c77,'(29i1)') mcq
 | 
					
						
							|  |  |  |       mcq=2*mod(mcq+rvec(1:29),2)-1
 | 
					
						
							|  |  |  |       cqstr0=cqstr
 | 
					
						
							|  |  |  |    endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-08 16:44:18 -06:00
										 |  |  |    l1=index(mycall,char(0))
 | 
					
						
							|  |  |  |    if(l1.ne.0) mycall(l1:)=" "
 | 
					
						
							|  |  |  |    l1=index(hiscall,char(0))
 | 
					
						
							|  |  |  |    if(l1.ne.0) hiscall(l1:)=" "
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |    if(mycall.ne.mycall0 .or. hiscall.ne.hiscall0) then
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |       apbits=0
 | 
					
						
							|  |  |  |       apbits(1)=99
 | 
					
						
							|  |  |  |       apbits(30)=99
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |       apmy_ru=0
 | 
					
						
							|  |  |  |       aphis_fd=0
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  |       if(len(trim(mycall)) .lt. 3) go to 10 
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |       nohiscall=.false.
 | 
					
						
							|  |  |  |       hiscall0=hiscall
 | 
					
						
							|  |  |  |       if(len(trim(hiscall0)).lt.3) then
 | 
					
						
							|  |  |  |          hiscall0=mycall  ! use mycall for dummy hiscall - mycall won't be hashed.
 | 
					
						
							|  |  |  |          nohiscall=.true.
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |       endif
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |       message=trim(mycall)//' '//trim(hiscall0)//' RR73'
 | 
					
						
							| 
									
										
										
										
											2019-02-14 14:56:02 -05:00
										 |  |  |       i3=-1
 | 
					
						
							|  |  |  |       n3=-1
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |       call pack77(message,i3,n3,c77)
 | 
					
						
							|  |  |  |       call unpack77(c77,1,msgsent,unpk77_success)
 | 
					
						
							|  |  |  |       if(i3.ne.1 .or. (message.ne.msgsent) .or. .not.unpk77_success) go to 10 
 | 
					
						
							|  |  |  |       read(c77,'(77i1)') message77
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |       apmy_ru=2*mod(message77(1:28)+rvec(2:29),2)-1
 | 
					
						
							|  |  |  |       aphis_fd=2*mod(message77(30:57)+rvec(29:56),2)-1
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |       message77=mod(message77+rvec,2)
 | 
					
						
							|  |  |  |       call encode174_91(message77,cw)
 | 
					
						
							|  |  |  |       apbits=2*cw-1
 | 
					
						
							|  |  |  |       if(nohiscall) apbits(30)=99
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | 10    continue
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |       mycall0=mycall
 | 
					
						
							|  |  |  |       hiscall0=hiscall
 | 
					
						
							|  |  |  |    endif
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    candidate=0.0
 | 
					
						
							|  |  |  |    ncand=0
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:22:41 -05:00
										 |  |  |    syncmin=1.2
 | 
					
						
							|  |  |  |    maxcand=100
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-31 12:10:58 -05:00
										 |  |  |    fa=nfa
 | 
					
						
							|  |  |  |    fb=nfb
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |    call clockit('getcand4',0)
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:22:41 -05:00
										 |  |  |    call getcandidates4(iwave,fa,fb,syncmin,nfqso,maxcand,savg,candidate,   &
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |       ncand,sbase)
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |    call clockit('getcand4',1)
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:22:41 -05:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    ndecodes=0
 | 
					
						
							|  |  |  |    do icand=1,ncand
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |       f0=candidate(1,icand)
 | 
					
						
							| 
									
										
										
										
											2019-02-02 16:29:17 -06:00
										 |  |  |       snr=candidate(3,icand)-1.0
 | 
					
						
							| 
									
										
										
										
											2019-03-21 13:27:10 -05:00
										 |  |  |       if( f0.le.10.0 .or. f0.ge.4990.0 ) cycle
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |       call clockit('ft4_down',0)
 | 
					
						
							|  |  |  |       call ft4_downsample(iwave,f0,cd2)  !Downsample from 512 to 32 Sa/Symbol
 | 
					
						
							|  |  |  |       call clockit('ft4_down',1)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:47:01 -06:00
										 |  |  |       sum2=sum(cd2*conjg(cd2))/(real(NMAX)/real(NDOWN))
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |       if(sum2.gt.0.0) cd2=cd2/sqrt(sum2)
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:22:41 -05:00
										 |  |  | ! Sample rate is now 12000/16 = 750 samples/second
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:53:53 -06:00
										 |  |  |       do isync=1,2
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |          if(isync.eq.1) then
 | 
					
						
							| 
									
										
										
										
											2019-02-02 16:29:17 -06:00
										 |  |  |             idfmin=-12
 | 
					
						
							|  |  |  |             idfmax=12
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |             idfstp=3
 | 
					
						
							|  |  |  |             ibmin=0
 | 
					
						
							| 
									
										
										
										
											2019-02-21 10:08:18 -05:00
										 |  |  |             ibmax=216                     !Max DT = 216/750 = 0.288 s
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |             ibstp=4
 | 
					
						
							|  |  |  |          else
 | 
					
						
							| 
									
										
										
										
											2019-02-02 16:29:17 -06:00
										 |  |  |             idfmin=idfbest-4
 | 
					
						
							|  |  |  |             idfmax=idfbest+4
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |             idfstp=1
 | 
					
						
							|  |  |  |             ibmin=max(0,ibest-5)
 | 
					
						
							|  |  |  |             ibmax=min(ibest+5,NMAX/NDOWN-1)
 | 
					
						
							|  |  |  |             ibstp=1
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |          endif
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |          ibest=-1
 | 
					
						
							|  |  |  |          smax=-99.
 | 
					
						
							|  |  |  |          idfbest=0
 | 
					
						
							|  |  |  |          do idf=idfmin,idfmax,idfstp
 | 
					
						
							|  |  |  |             a=0.
 | 
					
						
							|  |  |  |             a(1)=real(idf)
 | 
					
						
							|  |  |  |             ctwk=1.
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |             call clockit('twkfreq1',0)
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |             call twkfreq1(ctwk,4*NSS,fs,a,ctwk2)
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |             call clockit('twkfreq1',1)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |             call clockit('sync4d  ',0)
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |             do istart=ibmin,ibmax,ibstp
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |                call sync4d(cd2,istart,ctwk2,1,sync,sync2)  !Find sync power
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |                if(sync.gt.smax) then
 | 
					
						
							|  |  |  |                   smax=sync
 | 
					
						
							|  |  |  |                   ibest=istart
 | 
					
						
							|  |  |  |                   idfbest=idf
 | 
					
						
							|  |  |  |                endif
 | 
					
						
							|  |  |  |             enddo
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |             call clockit('sync4d  ',1)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |          enddo
 | 
					
						
							|  |  |  |       enddo
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  |       f0=f0+real(idfbest)
 | 
					
						
							| 
									
										
										
										
											2019-03-21 13:27:10 -05:00
										 |  |  |       if( f0.le.10.0 .or. f0.ge.4990.0 ) cycle
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |       call clockit('ft4down ',0)
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:22:41 -05:00
										 |  |  |       call ft4_downsample(iwave,f0,cb) !Final downsample with corrected f0
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |       call clockit('ft4down ',1)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |       sum2=sum(abs(cb)**2)/(real(NSS)*NN)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |       if(sum2.gt.0.0) cb=cb/sqrt(sum2)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |       cd=cb(ibest:ibest+NN*NSS-1)
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |       call clockit('four2a  ',0)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |       do k=1,NN
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |          i1=(k-1)*NSS
 | 
					
						
							|  |  |  |          csymb=cd(i1:i1+NSS-1)
 | 
					
						
							|  |  |  |          call four2a(csymb,NSS,1,-1,1)
 | 
					
						
							|  |  |  |          cs(0:3,k)=csymb(1:4)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |          s4(0:3,k)=abs(csymb(1:4))
 | 
					
						
							|  |  |  |       enddo
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |       call clockit('four2a  ',1)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:22:41 -05:00
										 |  |  | ! Sync quality check
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |       is1=0
 | 
					
						
							|  |  |  |       is2=0
 | 
					
						
							|  |  |  |       is3=0
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |       is4=0
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |       do k=1,4
 | 
					
						
							|  |  |  |          ip=maxloc(s4(:,k))
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |          if(icos4a(k-1).eq.(ip(1)-1)) is1=is1+1
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |          ip=maxloc(s4(:,k+33))
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |          if(icos4b(k-1).eq.(ip(1)-1)) is2=is2+1
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |          ip=maxloc(s4(:,k+66))
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |          if(icos4c(k-1).eq.(ip(1)-1)) is3=is3+1
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |          ip=maxloc(s4(:,k+99))
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |          if(icos4d(k-1).eq.(ip(1)-1)) is4=is4+1
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |       enddo
 | 
					
						
							| 
									
										
										
										
											2019-03-26 14:00:32 -04:00
										 |  |  |       nsync=is1+is2+is3+is4   !Number of correct hard sync symbols, 0-16
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |       if(smax .lt. 0.7 .or. nsync .lt. 8) cycle
 | 
					
						
							| 
									
										
										
										
											2019-02-08 15:17:46 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-30 15:49:52 -05:00
										 |  |  |       do nseq=1,3             !Try coherent sequences of 1, 2, and 4 symbols
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |          if(nseq.eq.1) nsym=1
 | 
					
						
							|  |  |  |          if(nseq.eq.2) nsym=2
 | 
					
						
							|  |  |  |          if(nseq.eq.3) nsym=4
 | 
					
						
							|  |  |  |          nt=2**(2*nsym)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |          do ks=1,NN-nsym+1,nsym  !87+16=103 symbols.
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |             amax=-1.0
 | 
					
						
							|  |  |  |             do i=0,nt-1
 | 
					
						
							|  |  |  |                i1=i/64
 | 
					
						
							|  |  |  |                i2=iand(i,63)/16
 | 
					
						
							|  |  |  |                i3=iand(i,15)/4
 | 
					
						
							|  |  |  |                i4=iand(i,3)
 | 
					
						
							|  |  |  |                if(nsym.eq.1) then
 | 
					
						
							|  |  |  |                   s2(i)=abs(cs(graymap(i4),ks))
 | 
					
						
							|  |  |  |                elseif(nsym.eq.2) then
 | 
					
						
							|  |  |  |                   s2(i)=abs(cs(graymap(i3),ks)+cs(graymap(i4),ks+1))
 | 
					
						
							|  |  |  |                elseif(nsym.eq.4) then
 | 
					
						
							|  |  |  |                   s2(i)=abs(cs(graymap(i1),ks  ) + &
 | 
					
						
							|  |  |  |                      cs(graymap(i2),ks+1) + &
 | 
					
						
							|  |  |  |                      cs(graymap(i3),ks+2) + &
 | 
					
						
							|  |  |  |                      cs(graymap(i4),ks+3)   &
 | 
					
						
							|  |  |  |                      )
 | 
					
						
							|  |  |  |                else
 | 
					
						
							|  |  |  |                   print*,"Error - nsym must be 1, 2, or 4."
 | 
					
						
							|  |  |  |                endif
 | 
					
						
							|  |  |  |             enddo
 | 
					
						
							|  |  |  |             ipt=1+(ks-1)*2
 | 
					
						
							|  |  |  |             if(nsym.eq.1) ibmax=1
 | 
					
						
							|  |  |  |             if(nsym.eq.2) ibmax=3
 | 
					
						
							|  |  |  |             if(nsym.eq.4) ibmax=7
 | 
					
						
							|  |  |  |             do ib=0,ibmax
 | 
					
						
							|  |  |  |                bm=maxval(s2(0:nt-1),one(0:nt-1,ibmax-ib)) - &
 | 
					
						
							|  |  |  |                   maxval(s2(0:nt-1),.not.one(0:nt-1,ibmax-ib))
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |                if(ipt+ib.gt.2*NN) cycle
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |                if(nsym.eq.1) then
 | 
					
						
							|  |  |  |                   bmeta(ipt+ib)=bm
 | 
					
						
							|  |  |  |                elseif(nsym.eq.2) then
 | 
					
						
							|  |  |  |                   bmetb(ipt+ib)=bm
 | 
					
						
							|  |  |  |                elseif(nsym.eq.4) then
 | 
					
						
							|  |  |  |                   bmetc(ipt+ib)=bm
 | 
					
						
							|  |  |  |                endif
 | 
					
						
							|  |  |  |             enddo
 | 
					
						
							|  |  |  |          enddo
 | 
					
						
							|  |  |  |       enddo
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-14 17:34:46 -06:00
										 |  |  |       bmetb(205:206)=bmeta(205:206)
 | 
					
						
							|  |  |  |       bmetc(201:204)=bmetb(201:204)
 | 
					
						
							|  |  |  |       bmetc(205:206)=bmeta(205:206)
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |       call clockit('normaliz',0)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |       call normalizebmet(bmeta,2*NN)
 | 
					
						
							|  |  |  |       call normalizebmet(bmetb,2*NN)
 | 
					
						
							|  |  |  |       call normalizebmet(bmetc,2*NN)
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |       call clockit('normaliz',1)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  |       hbits=0
 | 
					
						
							|  |  |  |       where(bmeta.ge.0) hbits=1
 | 
					
						
							|  |  |  |       ns1=count(hbits(  1:  8).eq.(/0,0,0,1,1,0,1,1/))
 | 
					
						
							| 
									
										
										
										
											2019-02-05 19:18:50 -06:00
										 |  |  |       ns2=count(hbits( 67: 74).eq.(/0,1,0,0,1,1,1,0/))
 | 
					
						
							|  |  |  |       ns3=count(hbits(133:140).eq.(/1,1,1,0,0,1,0,0/))
 | 
					
						
							|  |  |  |       ns4=count(hbits(199:206).eq.(/1,0,1,1,0,0,0,1/))
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |       nsync_qual=ns1+ns2+ns3+ns4
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |       if(nsync_qual.lt. 20) cycle
 | 
					
						
							| 
									
										
										
										
											2019-01-27 19:19:47 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-26 23:03:54 -06:00
										 |  |  |       scalefac=2.83
 | 
					
						
							|  |  |  |       llra(  1: 58)=bmeta(  9: 66)
 | 
					
						
							|  |  |  |       llra( 59:116)=bmeta( 75:132)
 | 
					
						
							|  |  |  |       llra(117:174)=bmeta(141:198)
 | 
					
						
							|  |  |  |       llra=scalefac*llra
 | 
					
						
							|  |  |  |       llrb(  1: 58)=bmetb(  9: 66)
 | 
					
						
							|  |  |  |       llrb( 59:116)=bmetb( 75:132)
 | 
					
						
							|  |  |  |       llrb(117:174)=bmetb(141:198)
 | 
					
						
							|  |  |  |       llrb=scalefac*llrb
 | 
					
						
							|  |  |  |       llrc(  1: 58)=bmetc(  9: 66)
 | 
					
						
							|  |  |  |       llrc( 59:116)=bmetc( 75:132)
 | 
					
						
							|  |  |  |       llrc(117:174)=bmetc(141:198)
 | 
					
						
							|  |  |  |       llrc=scalefac*llrc
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |       apmag=maxval(abs(llra))*1.1
 | 
					
						
							|  |  |  |       npasses=3+nappasses(nQSOProgress)
 | 
					
						
							| 
									
										
										
										
											2019-02-08 15:17:46 -06:00
										 |  |  |       if(ncontest.ge.5) npasses=3  ! Don't support Fox and Hound
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |       do ipass=1,npasses
 | 
					
						
							|  |  |  |          if(ipass.eq.1) llr=llra
 | 
					
						
							|  |  |  |          if(ipass.eq.2) llr=llrb
 | 
					
						
							|  |  |  |          if(ipass.eq.3) llr=llrc
 | 
					
						
							|  |  |  |          if(ipass.le.3) then
 | 
					
						
							|  |  |  |             apmask=0
 | 
					
						
							|  |  |  |             iaptype=0
 | 
					
						
							|  |  |  |          endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |          if(ipass .gt. 3) then
 | 
					
						
							|  |  |  |             llrd=llrc
 | 
					
						
							|  |  |  |             iaptype=naptypes(nQSOProgress,ipass-3)
 | 
					
						
							| 
									
										
										
										
											2019-02-08 16:44:18 -06:00
										 |  |  | 
 | 
					
						
							|  |  |  | ! ncontest=0 : NONE
 | 
					
						
							|  |  |  | !          1 : NA_VHF
 | 
					
						
							|  |  |  | !          2 : EU_VHF
 | 
					
						
							|  |  |  | !          3 : FIELD DAY
 | 
					
						
							|  |  |  | !          4 : RTTY
 | 
					
						
							|  |  |  | !          5 : FOX
 | 
					
						
							|  |  |  | !          6 : HOUND
 | 
					
						
							|  |  |  | !
 | 
					
						
							|  |  |  | ! Conditions that cause us to bail out of AP decoding
 | 
					
						
							|  |  |  |             napwid=50
 | 
					
						
							|  |  |  |             if(ncontest.le.4 .and. iaptype.ge.3 .and. (abs(f0-nfqso).gt.napwid) ) cycle
 | 
					
						
							|  |  |  |             if(iaptype.ge.2 .and. apbits(1).gt.1) cycle  ! No, or nonstandard, mycall
 | 
					
						
							|  |  |  |             if(iaptype.ge.3 .and. apbits(30).gt.1) cycle ! No, or nonstandard, dxcall
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-03-04 17:10:57 -06:00
										 |  |  |             if(iaptype.eq.1) then  ! CQ or CQ TEST or CQ FD or CQ RU or CQ SCC
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                apmask=0
 | 
					
						
							|  |  |  |                apmask(1:29)=1
 | 
					
						
							| 
									
										
										
										
											2019-03-04 17:10:57 -06:00
										 |  |  |                llrd(1:29)=apmag*mcq(1:29)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |             endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |             if(iaptype.eq.2) then ! MyCall,???,???
 | 
					
						
							|  |  |  |                apmask=0
 | 
					
						
							|  |  |  |                if(ncontest.eq.0.or.ncontest.eq.1) then
 | 
					
						
							|  |  |  |                   apmask(1:29)=1
 | 
					
						
							|  |  |  |                   llrd(1:29)=apmag*apbits(1:29)
 | 
					
						
							|  |  |  |                else if(ncontest.eq.2) then
 | 
					
						
							|  |  |  |                   apmask(1:28)=1
 | 
					
						
							|  |  |  |                   llrd(1:28)=apmag*apbits(1:28)
 | 
					
						
							|  |  |  |                else if(ncontest.eq.3) then
 | 
					
						
							|  |  |  |                   apmask(1:28)=1
 | 
					
						
							|  |  |  |                   llrd(1:28)=apmag*apbits(1:28)
 | 
					
						
							|  |  |  |                else if(ncontest.eq.4) then
 | 
					
						
							|  |  |  |                   apmask(2:29)=1
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |                   llrd(2:29)=apmag*apmy_ru(1:28)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                endif
 | 
					
						
							|  |  |  |             endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |             if(iaptype.eq.3) then ! MyCall,DxCall,???
 | 
					
						
							|  |  |  |                apmask=0
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |                if(ncontest.eq.0.or.ncontest.eq.1.or.ncontest.eq.2) then
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                   apmask(1:58)=1
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |                   llrd(1:58)=apmag*apbits(1:58)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                else if(ncontest.eq.3) then ! Field Day
 | 
					
						
							|  |  |  |                   apmask(1:56)=1
 | 
					
						
							|  |  |  |                   llrd(1:28)=apmag*apbits(1:28)
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |                   llrd(29:56)=apmag*aphis_fd(1:28)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                else if(ncontest.eq.4) then ! RTTY RU
 | 
					
						
							|  |  |  |                   apmask(2:57)=1
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |                   llrd(2:29)=apmag*apmy_ru(1:28)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                   llrd(30:57)=apmag*apbits(30:57)
 | 
					
						
							|  |  |  |                endif
 | 
					
						
							|  |  |  |             endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |             if(iaptype.eq.4 .or. iaptype.eq.5 .or. iaptype.eq.6) then
 | 
					
						
							|  |  |  |                apmask=0
 | 
					
						
							| 
									
										
										
										
											2019-03-03 13:02:22 -06:00
										 |  |  |                if(ncontest.le.4) then
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |                   apmask(1:91)=1   ! mycall, hiscall, RRR|73|RR73
 | 
					
						
							|  |  |  |                   if(iaptype.eq.6) llrd(1:91)=apmag*apbits(1:91)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                endif
 | 
					
						
							|  |  |  |             endif
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |             llr=llrd
 | 
					
						
							|  |  |  |          endif
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |          max_iterations=40
 | 
					
						
							| 
									
										
										
										
											2019-02-14 18:54:14 -06:00
										 |  |  |          message77=0
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |          call clockit('bpdecode',0)
 | 
					
						
							|  |  |  |          call bpdecode174_91(llr,apmask,max_iterations,message77,     &
 | 
					
						
							|  |  |  |             cw,nharderror,niterations)
 | 
					
						
							|  |  |  |          call clockit('bpdecode',1)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |          if(sum(message77).eq.0) cycle
 | 
					
						
							|  |  |  |          if( nharderror.ge.0 ) then
 | 
					
						
							| 
									
										
										
										
											2019-02-09 16:08:39 -06:00
										 |  |  |             message77=mod(message77+rvec,2) ! remove rvec scrambling
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |             write(c77,'(77i1)') message77(1:77)
 | 
					
						
							|  |  |  |             call unpack77(c77,1,message,unpk77_success)
 | 
					
						
							|  |  |  |             idupe=0
 | 
					
						
							|  |  |  |             do i=1,ndecodes
 | 
					
						
							|  |  |  |                if(decodes(i).eq.message) idupe=1
 | 
					
						
							|  |  |  |             enddo
 | 
					
						
							| 
									
										
										
										
											2019-02-13 14:42:57 -05:00
										 |  |  |             if(ibest.le.10 .and. message.eq.msg0) idupe=1   !Already decoded
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |             if(idupe.eq.1) exit
 | 
					
						
							|  |  |  |             ndecodes=ndecodes+1
 | 
					
						
							|  |  |  |             decodes(ndecodes)=message
 | 
					
						
							| 
									
										
										
										
											2019-02-02 16:29:17 -06:00
										 |  |  |             if(snr.gt.0.0) then
 | 
					
						
							|  |  |  |                xsnr=10*log10(snr)-14.0
 | 
					
						
							|  |  |  |             else
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                xsnr=-20.0
 | 
					
						
							| 
									
										
										
										
											2019-02-02 16:29:17 -06:00
										 |  |  |             endif
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |             nsnr=nint(max(-20.0,xsnr))
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |             freq=f0
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  |             tsig=mod(tbuf + ibest/750.0,100.0)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  |             write(line,1000) hhmmss,nsnr,tsig,nint(freq),message
 | 
					
						
							|  |  |  | 1000        format(a6,i4,f5.1,i5,' + ',1x,a37)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |             l1=index(data_dir,char(0))-1
 | 
					
						
							| 
									
										
										
										
											2019-02-08 11:24:22 -06:00
										 |  |  |             if(l1.ge.1) data_dir(l1+1:l1+1)="/"
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |             fname=data_dir(1:l1+1)//'all_ft4.txt'
 | 
					
						
							| 
									
										
										
										
											2019-02-01 11:56:08 -05:00
										 |  |  |             open(24,file=trim(fname),status='unknown',position='append')
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  |             write(24,1002) cdatetime0,nsnr,tsig,nint(freq),message,    &
 | 
					
						
							| 
									
										
										
										
											2019-03-26 14:00:32 -04:00
										 |  |  |                nharderror,nsync_qual,ipass,niterations,iaptype,nsync
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |             if(hhmmss.eq.'      ') write(*,1002) cdatetime0,nsnr,             &
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |                tsig,nint(freq),message,nharderror,nsync_qual,ipass,    &
 | 
					
						
							|  |  |  |                niterations,iaptype
 | 
					
						
							| 
									
										
										
										
											2019-03-26 14:00:32 -04:00
										 |  |  | 1002        format(a17,i4,f5.1,i5,' Rx  ',a37,6i4)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |             close(24)
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  |             linex(ndecodes)=line
 | 
					
						
							| 
									
										
										
										
											2019-02-21 10:08:18 -05:00
										 |  |  |             if(ibest.ge.ibmax-15) msg0=message         !Possible dupe candidate
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |             exit
 | 
					
						
							|  |  |  |          endif
 | 
					
						
							| 
									
										
										
										
											2019-01-30 12:22:41 -05:00
										 |  |  |       enddo !Sequence estimation
 | 
					
						
							|  |  |  |    enddo    !Candidate list
 | 
					
						
							| 
									
										
										
										
											2019-02-01 10:47:47 -05:00
										 |  |  |    call clockit('ft4_deco',1)
 | 
					
						
							| 
									
										
										
										
											2019-02-07 18:48:38 -06:00
										 |  |  |    call clockit2(data_dir)
 | 
					
						
							|  |  |  |    call clockit('ft4_deco',101)
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  |    return
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-03-09 10:03:01 -06:00
										 |  |  |  entry get_ft4msg(idecode,line)
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  |    line=linex(idecode)
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  |    return
 | 
					
						
							| 
									
										
										
										
											2019-01-31 13:55:21 -05:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-01-26 11:42:07 -06:00
										 |  |  | end subroutine ft4_decode
 |