2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								program msk144d2
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ! Test the msk144 decoder for WSJT-X
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  use options
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  use timer_module, only: timer
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  use timer_impl, only: init_timer
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  use readwav
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  character c
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  character*80 line
							 | 
						
					
						
							
								
									
										
										
										
											2017-07-24 14:23:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  character*512 datadir
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-20 02:49:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  character*500 infile
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  character*12 mycall,hiscall
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  character*6 mygrid
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  character(len=500) optarg
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  logical :: display_help=.false.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  logical*1 bShMsgs
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-20 02:49:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  logical*1 bcontest
							 | 
						
					
						
							
								
									
										
										
										
											2017-07-24 14:23:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  logical*1 btrain
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-31 02:57:20 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  logical*1 bswl
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-20 02:49:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  type(wav_header) :: wav
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-20 02:49:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer*2 id2(30*12000)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer*2 ichunk(7*1024)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2017-07-24 14:23:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  real*8 pcoeffs(5)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-22 18:17:23 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  type (option) :: long_options(9) = [ &
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-28 22:13:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       option ('ndepth',.true.,'c','ndepth',''), &  
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       option ('dxcall',.true.,'d','hiscall',''), &  
							 | 
						
					
						
							
								
									
										
										
										
											2017-01-02 20:13:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       option ('evemode',.true.,'e','Must be used with -s.',''), &
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-25 00:16:29 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       option ('frequency',.true.,'f','rxfreq',''), &
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       option ('help',.false.,'h','Display this help message',''), &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       option ('mycall',.true.,'m','mycall',''), &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       option ('nftol',.true.,'n','nftol',''), &
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-22 18:17:23 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       option ('rxequalize',.false.,'r','Rx Equalize',''), &
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       option ('short',.false.,'s','enable Sh','') &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       ]
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  t0=0.0
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-28 22:13:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  ndepth=3
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ntol=100
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-25 00:16:29 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  nrxfreq=1500
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  mycall=''
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-21 16:04:08 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  mygrid='EN50WC'
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  hiscall=''
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  bShMsgs=.false.
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-20 02:49:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  bcontest=.false.
							 | 
						
					
						
							
								
									
										
										
										
											2017-07-24 14:23:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  btrain=.false.
							 | 
						
					
						
							
								
									
										
										
										
											2017-01-03 20:55:10 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  bswl=.false.
							 | 
						
					
						
							
								
									
										
										
										
											2017-07-24 14:23:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  datadir='.'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  pcoeffs=0.d0
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  do
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-22 18:17:23 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     call getopt('c:d:ef:hm:n:rs',long_options,c,optarg,narglen,nstat,noffset,nremain,.true.)
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     if( nstat .ne. 0 ) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        exit
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     end if
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     select case (c)
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-28 22:13:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     case ('c')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        read (optarg(:narglen), *) ndepth 
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     case ('d')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        read (optarg(:narglen), *) hiscall
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     case ('e')
							 | 
						
					
						
							
								
									
										
										
										
											2017-01-02 20:13:47 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        bswl=.true. 
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-25 00:16:29 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     case ('f')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        read (optarg(:narglen), *) nrxfreq
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     case ('h')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        display_help = .true.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     case ('m')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        read (optarg(:narglen), *) mycall
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     case ('n')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        read (optarg(:narglen), *) ntol
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-22 18:17:23 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     case ('r')
							 | 
						
					
						
							
								
									
										
										
										
											2017-07-24 14:23:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        btrain=.true. 
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     case ('s')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        bShMsgs=.true. 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     end select
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  end do
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(display_help .or. nstat.lt.0 .or. nremain.lt.1) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     print *, ''
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     print *, 'Usage: msk144d [OPTIONS] file1 [file2 ...]'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     print *, ''
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     print *, '       msk144 decode pre-recorded .WAV file(s)'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     print *, ''
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     print *, 'OPTIONS:'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do i = 1, size (long_options)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        call long_options(i) % print (6)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     end do
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     go to 999
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  call init_timer ('timer.out')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  call timer('msk144  ',0)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ndecoded=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  do ifile=noffset+1,noffset+nremain
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     call get_command_argument(ifile,optarg,narglen)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     infile=optarg(:narglen)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     call timer('read    ',0)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     call wav%read (infile)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     i1=index(infile,'.wav')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     if( i1 .eq. 0 ) i1=index(infile,'.WAV')
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     read(infile(i1-6:i1-1),*,err=998) nutc
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     inquire(FILE=infile,SIZE=isize)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     npts=min((isize-216)/2,360000)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     read(unit=wav%lun) id2(1:npts)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     close(unit=wav%lun)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     call timer('read    ',1)
							 | 
						
					
						
							
								
									
										
										
										
											2016-10-01 00:05:20 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     do i=1,npts-7*1024+1,7*512
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       ichunk=id2(i:i+7*1024-1)
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-22 00:03:44 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       tsec=(i-1)/12000.0
							 | 
						
					
						
							
								
									
										
										
										
											2016-10-23 17:37:44 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								       tt=sum(float(abs(id2(i:i+7*512-1))))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       if( tt .ne. 0.0 ) then
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-22 18:17:23 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         call mskrtd(ichunk,nutc,tsec,ntol,nrxfreq,ndepth,mycall,mygrid,hiscall,bShMsgs, &
							 | 
						
					
						
							
								
									
										
										
										
											2017-07-24 14:23:22 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								                     bcontest,btrain,pcoeffs,bswl,datadir,line)
							 | 
						
					
						
							
								
									
										
										
										
											2016-12-22 18:17:23 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								         if( index(line,"&") .ne. 0 .or.   &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              index(line,"^") .ne. 0 .or.   &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              index(line,"!") .ne. 0 .or.   &
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              index(line,"@") .ne. 0 ) then 
							 | 
						
					
						
							
								
									
										
										
										
											2016-10-23 17:37:44 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								           write(*,*) line
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								         endif
							 | 
						
					
						
							
								
									
										
										
										
											2016-09-20 20:22:48 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								       endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     enddo 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  call timer('msk144  ',1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  call timer('msk144  ',101)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  go to 999
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								998 print*,'Cannot read from file:'
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  print*,infile
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								999 continue
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								end program msk144d2
							 |