2012-05-22 13:09:48 -04:00
|
|
|
program m65
|
|
|
|
|
|
|
|
! Decoder for map65. Can run stand-alone, reading data from *.tf2 files;
|
|
|
|
! or as the back end of map65, with data placed in a shared memory region.
|
|
|
|
|
2021-04-30 15:22:41 -04:00
|
|
|
! Fortran logical units
|
|
|
|
!
|
|
|
|
! 10 binary input data, *.tf2 files
|
|
|
|
! 11 prefixes.txt
|
|
|
|
! 12
|
|
|
|
! 13 map65.log
|
|
|
|
! 14
|
|
|
|
! 15
|
2021-07-01 15:00:21 -04:00
|
|
|
! 16 tquick log
|
2021-04-30 15:22:41 -04:00
|
|
|
! 17 saved *.tf2 files
|
|
|
|
! 18 test file to be transmitted (wsjtgen.f90)
|
|
|
|
! 19 livecq.txt
|
|
|
|
! 20
|
|
|
|
! 21 map65_rx.log
|
|
|
|
! 22
|
|
|
|
! 23 CALL3.TXT
|
|
|
|
! 24
|
|
|
|
! 25
|
|
|
|
! 26 tmp26.txt
|
|
|
|
|
2021-04-29 09:39:08 -04:00
|
|
|
use timer_module, only: timer
|
|
|
|
use timer_impl, only: init_timer, fini_timer
|
|
|
|
|
2021-05-12 16:34:00 -04:00
|
|
|
parameter (NFFT=32768)
|
2012-05-22 13:09:48 -04:00
|
|
|
parameter (NSMAX=60*96000)
|
2021-04-16 15:12:00 -04:00
|
|
|
parameter (NREAD=2048)
|
|
|
|
integer*2 i2(NREAD)
|
2012-05-22 13:09:48 -04:00
|
|
|
real*8 hsym
|
|
|
|
real*4 ssz5a(NFFT)
|
|
|
|
logical*1 lstrong(0:1023)
|
|
|
|
real*8 fc0,fcenter
|
|
|
|
character*80 arg,infile
|
|
|
|
character mycall*12,hiscall*12,mygrid*6,hisgrid*6,datetime*20
|
2021-05-30 12:07:48 -04:00
|
|
|
common/datcom/dd(4,5760000),ss(4,322,NFFT),savg(4,NFFT),fc0,nutc0,junk(37)
|
2012-05-22 13:09:48 -04:00
|
|
|
common/npar/fcenter,nutc,idphi,mousedf,mousefqso,nagain, &
|
|
|
|
ndepth,ndiskdat,neme,newdat,nfa,nfb,nfcal,nfshift, &
|
2017-01-15 17:01:24 -05:00
|
|
|
mcall3,nkeep,ntol,nxant,nrxlog,nfsample,nxpol,nmode, &
|
2021-05-30 12:07:48 -04:00
|
|
|
nfast,nsave,max_drift,mycall,mygrid,hiscall,hisgrid,datetime
|
2012-05-22 13:09:48 -04:00
|
|
|
|
|
|
|
nargs=iargc()
|
2021-04-16 15:12:00 -04:00
|
|
|
if(nargs.ne.1 .and. nargs.lt.5) then
|
|
|
|
print*,'Usage: m65 Jsub Qsub Xpol <95238|96000> file1 [file2 ...]'
|
|
|
|
print*,'Examples: m65 B A X 96000 *.tf2'
|
|
|
|
print*,' m65 C C N 96000 *.iq'
|
2012-05-22 13:09:48 -04:00
|
|
|
print*,''
|
2021-04-16 15:12:00 -04:00
|
|
|
print*,' m65 -s'
|
2012-08-31 14:29:54 -04:00
|
|
|
print*,' (Gets data from MAP65, via shared memory region.)'
|
2012-05-22 13:09:48 -04:00
|
|
|
go to 999
|
|
|
|
endif
|
|
|
|
call getarg(1,arg)
|
|
|
|
if(arg(1:2).eq.'-s') then
|
|
|
|
call m65a
|
|
|
|
go to 999
|
|
|
|
endif
|
2021-04-16 15:12:00 -04:00
|
|
|
n=1
|
|
|
|
if(arg(1:1).eq.'0') n=0
|
|
|
|
if(arg(1:1).eq.'A') n=1
|
|
|
|
if(arg(1:1).eq.'B') n=2
|
|
|
|
if(arg(1:1).eq.'C') n=3
|
|
|
|
|
2012-08-31 14:29:54 -04:00
|
|
|
call getarg(2,arg)
|
2021-04-16 15:12:00 -04:00
|
|
|
m=1
|
|
|
|
if(arg(1:1).eq.'0') m=0
|
|
|
|
if(arg(1:1).eq.'A') m=1
|
|
|
|
if(arg(1:1).eq.'B') m=2
|
|
|
|
if(arg(1:1).eq.'C') m=3
|
|
|
|
if(arg(1:1).eq.'D') m=4
|
|
|
|
if(arg(1:1).eq.'E') m=5
|
|
|
|
nmode=10*m + n
|
|
|
|
|
|
|
|
call getarg(3,arg)
|
|
|
|
nxpol=0
|
|
|
|
if(arg(1:1).eq.'X') nxpol=1
|
2012-05-22 13:09:48 -04:00
|
|
|
|
2021-04-16 15:12:00 -04:00
|
|
|
call getarg(4,arg)
|
|
|
|
nfsample=96000
|
|
|
|
if(arg.eq.'95238') nfsample=95238
|
|
|
|
|
|
|
|
ifile1=5
|
2021-04-28 13:36:48 -04:00
|
|
|
|
|
|
|
! Some default parameters for command-line execution, in early testing.
|
2021-04-16 15:12:00 -04:00
|
|
|
mycall='K1JT'
|
|
|
|
mygrid='FN20QI'
|
|
|
|
hiscall='K9AN'
|
|
|
|
hisgrid='EN50'
|
2021-04-29 12:13:17 -04:00
|
|
|
nfa=100 !144.100
|
|
|
|
nfb=162 !144.162
|
2021-04-28 13:53:16 -04:00
|
|
|
ntol=100
|
2021-04-29 12:13:17 -04:00
|
|
|
nkeep=10 !???
|
|
|
|
mousefqso=140 !For IK4WLV in 210220_1814.tf2
|
2021-04-29 17:05:11 -04:00
|
|
|
mousedf=0
|
2021-04-29 12:13:17 -04:00
|
|
|
nfcal=0
|
2021-04-29 17:05:11 -04:00
|
|
|
nkhz_center=125
|
2021-04-16 15:12:00 -04:00
|
|
|
|
|
|
|
if(nxpol.eq.0) then
|
2021-04-29 12:13:17 -04:00
|
|
|
nfa=55 !For KA1GT files
|
2021-04-16 15:12:00 -04:00
|
|
|
nfb=143
|
2021-04-29 17:05:11 -04:00
|
|
|
mousefqso=69 !W2HRO signal
|
|
|
|
nkhz_center=100
|
2021-04-16 15:12:00 -04:00
|
|
|
endif
|
2012-05-22 13:09:48 -04:00
|
|
|
|
2021-04-20 12:45:41 -04:00
|
|
|
call ftninit('.')
|
2021-04-29 09:39:08 -04:00
|
|
|
call init_timer('timer.out')
|
|
|
|
call timer('m65 ',0)
|
|
|
|
|
2012-05-22 13:09:48 -04:00
|
|
|
do ifile=ifile1,nargs
|
|
|
|
call getarg(ifile,infile)
|
|
|
|
open(10,file=infile,access='stream',status='old',err=998)
|
|
|
|
i1=index(infile,'.tf2')
|
2021-04-16 15:12:00 -04:00
|
|
|
if(i1.lt.1) i1=index(infile,'.iq')
|
2012-05-22 13:09:48 -04:00
|
|
|
read(infile(i1-4:i1-1),*,err=1) nutc0
|
|
|
|
go to 2
|
|
|
|
1 nutc0=0
|
|
|
|
2 hsym=2048.d0*96000.d0/11025.d0 !Samples per half symbol
|
2021-04-16 15:12:00 -04:00
|
|
|
read(10) fcenter
|
|
|
|
newdat=1
|
2012-05-22 13:09:48 -04:00
|
|
|
nhsym0=-999
|
|
|
|
k=0
|
2021-04-16 15:12:00 -04:00
|
|
|
|
|
|
|
nch=2
|
|
|
|
if(nxpol.eq.1) nch=4
|
2012-05-22 13:09:48 -04:00
|
|
|
|
|
|
|
do irec=1,9999999
|
2021-04-16 15:12:00 -04:00
|
|
|
read(10,end=10) i2
|
|
|
|
do i=1,NREAD,nch
|
2012-05-22 13:09:48 -04:00
|
|
|
k=k+1
|
2021-04-27 17:02:39 -04:00
|
|
|
if(k.gt.60*96000) exit
|
2021-04-16 15:12:00 -04:00
|
|
|
dd(1,k)=i2(i)
|
|
|
|
dd(2,k)=i2(i+1)
|
|
|
|
if(nxpol.eq.1) then
|
|
|
|
dd(3,k)=i2(i+2)
|
|
|
|
dd(4,k)=i2(i+3)
|
|
|
|
endif
|
2012-05-22 13:09:48 -04:00
|
|
|
enddo
|
|
|
|
nhsym=(k-2048)/hsym
|
|
|
|
if(nhsym.ge.1 .and. nhsym.ne.nhsym0) then
|
|
|
|
ndiskdat=1
|
|
|
|
nb=0
|
|
|
|
! Emit signal readyForFFT
|
|
|
|
fgreen=-13.0
|
2012-08-31 14:29:54 -04:00
|
|
|
iqadjust=0
|
|
|
|
iqapply=0
|
2012-05-22 13:09:48 -04:00
|
|
|
nbslider=100
|
|
|
|
gainx=0.9962
|
|
|
|
gainy=1.0265
|
|
|
|
phasex=0.01426
|
|
|
|
phasey=-0.01195
|
2021-04-16 15:12:00 -04:00
|
|
|
call timer('symspec ',0)
|
2017-01-17 13:45:23 -05:00
|
|
|
call symspec(k,nxpol,ndiskdat,nb,nbslider,idphi,nfsample, &
|
2012-09-04 16:11:26 -04:00
|
|
|
fgreen,iqadjust,iqapply,gainx,gainy,phasex,phasey,rejectx, &
|
|
|
|
rejecty,pxdb,pydb,ssz5a,nkhz,ihsym,nzap,slimit,lstrong)
|
2012-05-22 13:09:48 -04:00
|
|
|
call timer('symspec ',1)
|
|
|
|
nhsym0=nhsym
|
|
|
|
endif
|
2021-04-29 14:35:19 -04:00
|
|
|
enddo ! irec
|
2012-05-22 13:09:48 -04:00
|
|
|
|
|
|
|
10 continue
|
|
|
|
if(iqadjust.ne.0) write(*,3002) rejectx,rejecty
|
|
|
|
3002 format('Image rejection:',2f7.1,' dB')
|
|
|
|
nutc=nutc0
|
|
|
|
nstandalone=1
|
2021-04-16 15:12:00 -04:00
|
|
|
call decode0(dd,ss,savg,nstandalone)
|
2021-04-29 14:35:19 -04:00
|
|
|
enddo ! ifile
|
2012-05-22 13:09:48 -04:00
|
|
|
|
|
|
|
call timer('m65 ',1)
|
|
|
|
call timer('m65 ',101)
|
|
|
|
go to 999
|
|
|
|
|
|
|
|
998 print*,'Cannot open file:'
|
|
|
|
print*,infile
|
|
|
|
|
2021-04-29 09:39:08 -04:00
|
|
|
999 call fini_timer()
|
|
|
|
|
|
|
|
end program m65
|