FST4W: Add -Y option to jt9, which is like -W except that 22-bit hash values are printed for type 3 decodes.

This commit is contained in:
Steven Franke 2023-02-14 15:55:19 -06:00
parent 0a139e5acd
commit cbe674bedd
3 changed files with 31 additions and 21 deletions

View File

@ -44,6 +44,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
real ss(184,NSMAX) real ss(184,NSMAX)
logical baddata,newdat65,newdat9,single_decode,bVHF,bad0,newdat,ex logical baddata,newdat65,newdat9,single_decode,bVHF,bad0,newdat,ex
logical lprinthash22
integer*2 id2(NTMAX*12000) integer*2 id2(NTMAX*12000)
type(params_block) :: params type(params_block) :: params
real*4 dd(NTMAX*12000) real*4 dd(NTMAX*12000)
@ -221,27 +222,30 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
! We're in FST4 mode ! We're in FST4 mode
ndepth=iand(params%ndepth,3) ndepth=iand(params%ndepth,3)
iwspr=0 iwspr=0
lprinthash22=.false.
params%nsubmode=0 params%nsubmode=0
call timer('dec_fst4',0) call timer('dec_fst4',0)
call my_fst4%decode(fst4_decoded,id2,params%nutc, & call my_fst4%decode(fst4_decoded,id2,params%nutc, &
params%nQSOProgress,params%nfa,params%nfb, & params%nQSOProgress,params%nfa,params%nfb, &
params%nfqso,ndepth,params%ntr,params%nexp_decode, & params%nfqso,ndepth,params%ntr,params%nexp_decode, &
params%ntol,params%emedelay,logical(params%nagain), & params%ntol,params%emedelay,logical(params%nagain), &
logical(params%lapcqonly),mycall,hiscall,iwspr) logical(params%lapcqonly),mycall,hiscall,iwspr,lprinthash22)
call timer('dec_fst4',1) call timer('dec_fst4',1)
go to 800 go to 800
endif endif
if(params%nmode.eq.241) then if(params%nmode.eq.241 .or. params%nmode.eq.242) then
! We're in FST4W mode ! We're in FST4W mode
ndepth=iand(params%ndepth,3) ndepth=iand(params%ndepth,3)
iwspr=1 iwspr=1
lprinthash22=.false.
if(params%nmode.eq.242) lprinthash22=.true.
call timer('dec_fst4',0) call timer('dec_fst4',0)
call my_fst4%decode(fst4_decoded,id2,params%nutc, & call my_fst4%decode(fst4_decoded,id2,params%nutc, &
params%nQSOProgress,params%nfa,params%nfb, & params%nQSOProgress,params%nfa,params%nfb, &
params%nfqso,ndepth,params%ntr,params%nexp_decode, & params%nfqso,ndepth,params%ntr,params%nexp_decode, &
params%ntol,params%emedelay,logical(params%nagain), & params%ntol,params%emedelay,logical(params%nagain), &
logical(params%lapcqonly),mycall,hiscall,iwspr) logical(params%lapcqonly),mycall,hiscall,iwspr,lprinthash22)
call timer('dec_fst4',1) call timer('dec_fst4',1)
go to 800 go to 800
endif endif
@ -705,7 +709,7 @@ contains
end subroutine ft4_decoded end subroutine ft4_decoded
subroutine fst4_decoded (this,nutc,sync,nsnr,dt,freq,decoded,nap, & subroutine fst4_decoded (this,nutc,sync,nsnr,dt,freq,decoded,nap, &
qual,ntrperiod,lwspr,fmid,w50) qual,ntrperiod,fmid,w50)
use fst4_decode use fst4_decode
implicit none implicit none
@ -720,7 +724,6 @@ contains
integer, intent(in) :: nap integer, intent(in) :: nap
real, intent(in) :: qual real, intent(in) :: qual
integer, intent(in) :: ntrperiod integer, intent(in) :: ntrperiod
logical, intent(in) :: lwspr
real, intent(in) :: fmid real, intent(in) :: fmid
real, intent(in) :: w50 real, intent(in) :: w50

View File

@ -8,7 +8,7 @@ module fst4_decode
abstract interface abstract interface
subroutine fst4_decode_callback (this,nutc,sync,nsnr,dt,freq, & subroutine fst4_decode_callback (this,nutc,sync,nsnr,dt,freq, &
decoded,nap,qual,ntrperiod,lwspr,fmid,w50) decoded,nap,qual,ntrperiod,fmid,w50)
import fst4_decoder import fst4_decoder
implicit none implicit none
class(fst4_decoder), intent(inout) :: this class(fst4_decoder), intent(inout) :: this
@ -21,7 +21,6 @@ module fst4_decode
integer, intent(in) :: nap integer, intent(in) :: nap
real, intent(in) :: qual real, intent(in) :: qual
integer, intent(in) :: ntrperiod integer, intent(in) :: ntrperiod
logical, intent(in) :: lwspr
real, intent(in) :: fmid real, intent(in) :: fmid
real, intent(in) :: w50 real, intent(in) :: w50
end subroutine fst4_decode_callback end subroutine fst4_decode_callback
@ -31,7 +30,7 @@ contains
subroutine decode(this,callback,iwave,nutc,nQSOProgress,nfa,nfb,nfqso, & subroutine decode(this,callback,iwave,nutc,nQSOProgress,nfa,nfb,nfqso, &
ndepth,ntrperiod,nexp_decode,ntol,emedelay,lagain,lapcqonly,mycall, & ndepth,ntrperiod,nexp_decode,ntol,emedelay,lagain,lapcqonly,mycall, &
hiscall,iwspr) hiscall,iwspr,lprinthash22)
use prog_args use prog_args
use timer_module, only: timer use timer_module, only: timer
@ -67,9 +66,10 @@ contains
integer mcq(29),mrrr(19),m73(19),mrr73(19) integer mcq(29),mrrr(19),m73(19),mrr73(19)
logical badsync,unpk77_success,single_decode logical badsync,unpk77_success,single_decode
logical first,nohiscall,lwspr logical first,nohiscall
logical new_callsign,plotspec_exists,wcalls_exists,do_k50_decode logical new_callsign,plotspec_exists,wcalls_exists,do_k50_decode
logical decdata_exists logical decdata_exists
logical lprinthash22
integer*2 iwave(30*60*12000) integer*2 iwave(30*60*12000)
@ -88,7 +88,8 @@ contains
dxcall13=hiscall ! initialize for use in packjt77 dxcall13=hiscall ! initialize for use in packjt77
mycall13=mycall mycall13=mycall
if(iwspr.ne.0.and.iwspr.ne.1) return if(iwspr.ne.0 .and. iwspr.ne.1) return
if(lagain) continue ! use lagain to keep compiler happy if(lagain) continue ! use lagain to keep compiler happy
if(first) then if(first) then
@ -503,6 +504,13 @@ contains
write(c77,'(50i1)') message74(1:50) write(c77,'(50i1)') message74(1:50)
c77(51:77)='000000000000000000000110000' c77(51:77)='000000000000000000000110000'
call unpack77(c77,1,msg,unpk77_success) call unpack77(c77,1,msg,unpk77_success)
if(lprinthash22 .and. unpk77_success .and. index(msg,'<...>').gt.0) then
read(c77,'(b22.22)') n22tmp
i1=index(msg,' ')
wpart=trim(msg(i1+1:))
write(msg,'(a1,i7.7,a1)') '<',n22tmp,'>'
msg=trim(msg)//' '//trim(wpart)
endif
if(unpk77_success .and. do_k50_decode) then if(unpk77_success .and. do_k50_decode) then
! If decode was obtained with Keff=66, save call/grid in fst4w_calls.txt if not there already. ! If decode was obtained with Keff=66, save call/grid in fst4w_calls.txt if not there already.
i1=index(msg,' ') i1=index(msg,' ')
@ -626,8 +634,7 @@ contains
close(21) close(21)
endif endif
call this%callback(nutc,smax1,nsnr,xdt,fsig,msg, & call this%callback(nutc,smax1,nsnr,xdt,fsig,msg, &
iaptype,qual,ntrperiod,lwspr,fmid,w50) iaptype,qual,ntrperiod,fmid,w50)
! if(iwspr.eq.0 .and. nb.lt.0) go to 900
goto 800 goto 800
endif endif
enddo ! metrics enddo ! metrics

View File

@ -27,7 +27,7 @@ program jt9
logical :: read_files = .true., tx9 = .false., display_help = .false., & logical :: read_files = .true., tx9 = .false., display_help = .false., &
bLowSidelobes = .false., nexp_decode_set = .false., & bLowSidelobes = .false., nexp_decode_set = .false., &
have_ntol = .false. have_ntol = .false.
type (option) :: long_options(31) = [ & type (option) :: long_options(32) = [ &
option ('help', .false., 'h', 'Display this help message', ''), & option ('help', .false., 'h', 'Display this help message', ''), &
option ('shmem',.true.,'s','Use shared memory for sample data','KEY'), & option ('shmem',.true.,'s','Use shared memory for sample data','KEY'), &
option ('tr-period', .true., 'p', 'Tx/Rx period, default SECONDS=60', & option ('tr-period', .true., 'p', 'Tx/Rx period, default SECONDS=60', &
@ -60,6 +60,7 @@ program jt9
option ('jt65', .false.,'6', 'JT65 mode', ''), & option ('jt65', .false.,'6', 'JT65 mode', ''), &
option ('fst4', .false., '7', 'FST4 mode', ''), & option ('fst4', .false., '7', 'FST4 mode', ''), &
option ('fst4w', .false., 'W', 'FST4W mode', ''), & option ('fst4w', .false., 'W', 'FST4W mode', ''), &
option ('fst4w', .false., 'Y', 'FST4W mode, print hash22 values', ''), &
option ('ft8', .false., '8', 'FT8 mode', ''), & option ('ft8', .false., '8', 'FT8 mode', ''), &
option ('jt9', .false., '9', 'JT9 mode', ''), & option ('jt9', .false., '9', 'JT9 mode', ''), &
option ('qra64', .false., 'q', 'QRA64 mode', ''), & option ('qra64', .false., 'q', 'QRA64 mode', ''), &
@ -85,13 +86,12 @@ program jt9
common/decstats/ntry65a,ntry65b,n65a,n65b,num9,numfano common/decstats/ntry65a,ntry65b,n65a,n65b,num9,numfano
data npatience/1/,nthreads/1/,wisfile/' '/ data npatience/1/,nthreads/1/,wisfile/' '/
iwspr=0
nsubmode = 0 nsubmode = 0
ntol = 20 ntol = 20
TRperiod=60.d0 TRperiod=60.d0
do do
call getopt('hs:e:a:b:r:m:p:d:f:F:w:t:9876543WqTL:S:H:c:G:x:g:X:Q:', & call getopt('hs:e:a:b:r:m:p:d:f:F:w:t:9876543WYqTL:S:H:c:G:x:g:X:Q:', &
long_options,c,optarg,arglen,stat,offset,remain,.true.) long_options,c,optarg,arglen,stat,offset,remain,.true.)
if (stat .ne. 0) then if (stat .ne. 0) then
exit exit
@ -141,7 +141,6 @@ program jt9
if (mode.lt.65) mode = mode + 65 if (mode.lt.65) mode = mode + 65
case ('7') case ('7')
mode = 240 mode = 240
iwspr=0
case ('8') case ('8')
mode = 8 mode = 8
case ('9') case ('9')
@ -152,7 +151,8 @@ program jt9
read (optarg(:arglen), *) npatience read (optarg(:arglen), *) npatience
case ('W') case ('W')
mode = 241 mode = 241
iwspr=1 case ('Y')
mode = 242
case ('c') case ('c')
read (optarg(:arglen), *) mycall read (optarg(:arglen), *) mycall
case ('G') case ('G')
@ -212,7 +212,7 @@ program jt9
hisgrid=' ' hisgrid=' '
endif endif
if (mode .eq. 241) then if (mode .eq. 241 .or. mode .eq. 242) then
ntol = min (ntol, 100) ntol = min (ntol, 100)
else if (mode .eq. 65 + 9 .and. .not. have_ntol) then else if (mode .eq. 65 + 9 .and. .not. have_ntol) then
ntol = 20 ntol = 20
@ -222,7 +222,7 @@ program jt9
ntol = min (ntol, 1000) ntol = min (ntol, 1000)
end if end if
if (.not. nexp_decode_set) then if (.not. nexp_decode_set) then
if (mode .eq. 240 .or. mode .eq. 241) then if (mode .eq. 240 .or. mode .eq. 241 .or. mode .eq. 242) then
nexp_decode = 3 * 256 ! single decode off and nb=0 nexp_decode = 3 * 256 ! single decode off and nb=0
end if end if
end if end if
@ -277,7 +277,8 @@ program jt9
call timer('symspec ',1) call timer('symspec ',1)
endif endif
nhsym0=nhsym nhsym0=nhsym
if(nhsym.ge.181 .and. mode.ne.240 .and. mode.ne.241 .and. mode.ne.66) exit if(nhsym.ge.181 .and. mode.ne.240 .and. mode.ne.241 .and. &
mode.ne.242 .and. mode.ne.66) exit
endif endif
enddo enddo
close(unit=wav%lun) close(unit=wav%lun)
@ -294,7 +295,6 @@ program jt9
shared_data%params%kin=64800 shared_data%params%kin=64800
if(mode.eq.240) shared_data%params%kin=720000 !### 60 s periods ### if(mode.eq.240) shared_data%params%kin=720000 !### 60 s periods ###
shared_data%params%nzhsym=nhsym shared_data%params%nzhsym=nhsym
if(mode.eq.240 .and. iwspr.eq.1) ndepth=ior(ndepth,128)
shared_data%params%ndepth=ndepth shared_data%params%ndepth=ndepth
shared_data%params%lft8apon=.true. shared_data%params%lft8apon=.true.
shared_data%params%ljt65apon=.true. shared_data%params%ljt65apon=.true.