2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								module jt65_test
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ! Test the JT65 decoder for WSJT-X
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  implicit none
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  public :: test
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer, parameter, public :: NZMAX=60*12000
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer, public :: nft
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								contains
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  subroutine test (dd,nutc,nflow,nfhigh,nfqso,ntol,nsubmode,n2pass,nrobust     &
							 | 
						
					
						
							
								
									
										
										
										
											2017-11-04 17:03:56 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       ,ntrials,naggressive,ndepth,mycall,hiscall,hisgrid,nexp_decode,         &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        nQSOProgress,ljt65apon)
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    use timer_module, only: timer
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    use jt65_decode
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    implicit none
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    include 'constants.f90'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    real, intent(in) :: dd(NZMAX)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    integer, intent(in) :: nutc, nflow, nfhigh, nfqso, ntol, nsubmode, n2pass  &
							 | 
						
					
						
							
								
									
										
										
										
											2017-11-04 00:40:08 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         , ntrials, naggressive, ndepth, nexp_decode, nQSOProgress
							 | 
						
					
						
							
								
									
										
										
										
											2017-11-04 17:03:56 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    logical, intent(in) :: nrobust,ljt65apon
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    character(len=12), intent(in) :: mycall, hiscall
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    character(len=6), intent(in) :: hisgrid
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    type(jt65_decoder) :: my_decoder
							 | 
						
					
						
							
								
									
										
										
										
											2016-04-06 17:11:19 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    logical nclearave                          !### Should be a dummy arg?
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    nclearave=.false.
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    call timer('jt65a   ',0)
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    call my_decoder%decode(my_callback,dd,npts=52*12000,newdat=.true.,     &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								         nutc=nutc,nf1=nflow,nf2=nfhigh,nfqso=nfqso,ntol=ntol,             &
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         nsubmode=nsubmode, minsync=-1,nagain=.false.,n2pass=n2pass,       &
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-09 21:01:28 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         nrobust=nrobust,ntrials=ntrials,naggressive=naggressive,          &
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-22 20:51:27 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         ndepth=ndepth,emedelay=0.0,clearave=nclearave,mycall=mycall,      &
							 | 
						
					
						
							
								
									
										
										
										
											2017-11-04 00:40:08 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         hiscall=hiscall,hisgrid=hisgrid,nexp_decode=nexp_decode,          &
							 | 
						
					
						
							
								
									
										
										
										
											2017-11-04 17:03:56 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         nQSOProgress=nQSOProgress,ljt65apon=ljt65apon)
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    call timer('jt65a   ',1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  end subroutine test
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  subroutine my_callback (this,sync,snr,dt,freq,drift,nflip,width,     &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       decoded,ft,qual,smo,sum,minsync)
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +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
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    character(len=22), intent(in) :: decoded
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    integer, intent(in) :: ft
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    integer, intent(in) :: qual
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-09 22:39:13 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    integer, intent(in) :: smo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    integer, intent(in) :: sum
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    integer, intent(in) :: minsync
							 | 
						
					
						
							
								
									
										
										
										
											2016-05-05 00:00:54 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    integer nwidth
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-17 18:52:06 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    real t
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2016-06-10 14:18:10 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    if(minsync+nflip+qual.eq.-9999) stop            !Silence compiler warning
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-17 18:52:06 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    t=max(0.0,width*width-7.2)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    nwidth=max(nint(sqrt(t)),2)
							 | 
						
					
						
							
								
									
										
										
										
											2016-05-03 16:10:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								!### deal with nflip here! ###
							 | 
						
					
						
							
								
									
										
										
										
											2016-05-05 00:00:54 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								!### also single_decode, csync, etc... ###
							 | 
						
					
						
							
								
									
										
										
										
											2017-10-30 21:30:14 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    write(*,1012) nint(sync),snr,dt,freq,drift,nwidth,         &
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-17 13:28:57 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         decoded,ft,sum,smo
							 | 
						
					
						
							
								
									
										
										
										
											2016-05-05 01:32:30 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								1012 format(i4,i5,f6.2,i5,i4,i3,1x,a22,' JT65',3i3)
							 | 
						
					
						
							
								
									
										
										
										
											2016-03-21 16:14:20 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								    nft=ft
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								    call flush(6)
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-31 01:30:31 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2015-12-29 23:54:40 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  end subroutine my_callback
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								end module jt65_test
							 |