2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								subroutine decoder(ss,id2,nfsample)
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  use prog_args
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-05 22:07:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  !$ use omp_lib
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  include 'constants.f90'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  real ss(184,NSMAX)
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  logical baddata
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer*2 id2(NTMAX*12000)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  real*4 dd(NTMAX*12000)
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  character datetime*20,mycall*12,mygrid*6,hiscall*12,hisgrid*6
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  common/npar/nutc,ndiskdat,ntrperiod,nfqso,newdat,npts8,nfa,nfsplit,nfb,    &
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       ntol,kin,nzhsym,nsubmode,nagain,ndepth,ntxmode,nmode,minw,nclearave,  &
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-24 15:05:45 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       minsync,emedelay,dttol,nlist,listutc(10),n2pass,nranera,naggressive,  &
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-25 20:09:57 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       nrobust,nexp_decode,nspare(9),datetime,mycall,mygrid,hiscall,hisgrid
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  common/tracer/limtrace,lu
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-05 22:07:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer onlevel(0:10)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  common/tracer_priv/level,onlevel
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-18 01:28:12 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								!$omp threadprivate(/tracer_priv/)
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  save
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-24 15:05:45 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  if(mod(n,2).eq.0) ntrials=10**(nranera/2)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(mod(n,2).eq.1) ntrials=3*10**(nranera/2)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(nranera.eq.0) ntrials=0
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-18 01:28:12 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-24 20:19:04 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  rms=sqrt(dot_product(float(id2(300000:310000)),                            &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								                       float(id2(300000:310000)))/10000.0)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(rms.lt.2.0) go to 800 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  if (nagain .eq. 0) then
							 | 
						
					
						
							
								
									
										
										
										
											2014-12-03 00:06:54 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     open(13,file=trim(temp_dir)//'/decoded.txt',status='unknown')
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  else
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-01 16:23:36 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     open(13,file=trim(temp_dir)//'/decoded.txt',status='unknown',      &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								          position='append')
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  end if
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  if(nmode.eq.4 .or. nmode.eq.65) open(14,file=trim(temp_dir)//'/avemsg.txt', &
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-01 16:23:36 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       status='unknown')
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  if(nmode.eq.4) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     jz=52*nfsample
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     if(newdat.ne.0) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(nfsample.eq.12000) call wav11(id2,jz,dd)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(nfsample.eq.11025) dd(1:jz)=id2(1:jz)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     endif
							 | 
						
					
						
							
								
									
										
										
										
											2015-05-27 13:08:28 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     call jt4a(dd,jz,nutc,nfqso,ntol,emedelay,dttol,nagain,ndepth,       &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								          nclearave,minsync,minw,nsubmode,mycall,hiscall,hisgrid,        &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								          nlist,listutc)
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     go to 800
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  npts65=52*12000
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(baddata(id2,npts65)) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     nsynced=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     ndecoded=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     go to 800
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-18 01:28:12 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  ntol65=ntol              !### is this OK? ###
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-08 15:07:31 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  newdat65=newdat
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  newdat9=newdat
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								!$ call omp_set_dynamic(.true.)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								!$omp parallel sections num_threads(2) copyin(/tracer_priv/) shared(ndecoded) if(.true.) !iif() needed on Mac
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								!$omp section
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(nmode.eq.65 .or. (nmode.eq.(65+9) .and. ntxmode.eq.65)) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! We're in JT65 mode, or should do JT65 first
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-08 15:07:31 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     if(newdat65.ne.0) dd(1:npts65)=id2(1:npts65)
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     nf1=nfa
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     nf2=nfb
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-01 20:11:10 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     call timer('jt65a   ',0)
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     call jt65a(dd,npts65,newdat65,nutc,nf1,nf2,nfqso,ntol65,nsubmode,      &
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-25 20:09:57 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								          minsync,nagain,n2pass,nrobust,ntrials,naggressive,ndepth,         &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								          nexp_decode,ndecoded)
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-01 20:11:10 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     call timer('jt65a   ',1)
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  else if(nmode.eq.9 .or. (nmode.eq.(65+9) .and. ntxmode.eq.9)) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! We're in JT9 mode, or should do JT9 first
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     call timer('decjt9  ',0)
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-08 15:07:31 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     call decjt9(ss,id2,nutc,nfqso,newdat9,npts8,nfa,nfsplit,nfb,ntol,nzhsym,  &
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								          nagain,ndepth,nmode)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     call timer('decjt9  ',1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								!$omp section
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(nmode.eq.(65+9)) then          !Do the other mode (we're in dual mode)
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     if (ntxmode.eq.9) then
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-08 15:07:31 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        if(newdat65.ne.0) dd(1:npts65)=id2(1:npts65)
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        nf1=nfa
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        nf2=nfb
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        call timer('jt65a   ',0)
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        call jt65a(dd,npts65,newdat65,nutc,nf1,nf2,nfqso,ntol65,nsubmode,   &
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-25 20:09:57 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								             minsync,nagain,n2pass,nrobust,ntrials,naggressive,ndepth,      &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								             nexp_decode,ndecoded)
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        call timer('jt65a   ',1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     else
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        call timer('decjt9  ',0)
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-08 15:07:31 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        call decjt9(ss,id2,nutc,nfqso,newdat9,npts8,nfa,nfsplit,nfb,ntol,   &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								             nzhsym,nagain,ndepth,nmode)
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-04 15:34:46 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        call timer('decjt9  ',1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     end if
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								!$omp end parallel sections
							 | 
						
					
						
							
								
									
										
										
										
											2015-02-01 16:23:36 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2014-10-30 19:29:16 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								! JT65 is not yet producing info for nsynced, ndecoded.
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								800 write(*,1010) nsynced,ndecoded
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								1010 format('<DecodeFinished>',2i4)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  call flush(6)
							 | 
						
					
						
							
								
									
										
										
										
											2015-04-22 17:48:03 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  close(13) 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(nmode.eq.4 .or. nmode.eq.65) close(14)
							 | 
						
					
						
							
								
									
										
										
										
											2014-04-20 02:44:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  return
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								end subroutine decoder
							 |