Some changes to facilitate experimentation.

1. Send nQSOProgress into jt65 decoder.
2. Add experimental version of extract.f90.
3. Change CMakeFile.txt to use experimental routines.



git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@8217 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
Steven Franke 2017-11-04 00:40:08 +00:00
parent f072b5309c
commit a5e10b9967
8 changed files with 189 additions and 14 deletions

View File

@ -411,7 +411,7 @@ set (wsjt_FSRCS
lib/fsk4hf/encode300.f90
lib/entail.f90
lib/ephem.f90
lib/extract.f90
lib/fsk4hf/extract_ap.f90
lib/extract4.f90
lib/extractmessage144.f90
lib/fsk4hf/extractmessage168.f90
@ -605,7 +605,7 @@ set (qra_CSRCS
set (wsjt_CSRCS
${ka9q_CSRCS}
lib/ftrsd/ftrsd2.c
lib/fsk4hf/ftrsdap.c
lib/sgran.c
lib/golay24_table.c
lib/gran.c

View File

@ -1,5 +1,5 @@
subroutine decode65a(dd,npts,newdat,nqd,f0,nflip,mode65,ntrials, &
naggressive,ndepth,ntol,mycall,hiscall,hisgrid,nexp_decode, &
naggressive,ndepth,ntol,mycall,hiscall,hisgrid,nQSOProgress,nexp_decode, &
bVHF,sync2,a,dt,nft,nspecial,qual,nhist,nsmo,decoded)
! Apply AFC corrections to a candidate JT65 signal, then decode it.
@ -125,7 +125,8 @@ subroutine decode65a(dd,npts,newdat,nqd,f0,nflip,mode65,ntrials, &
nadd=ismo !### ??? ###
call decode65b(s2,nflip,nadd,mode65,ntrials,naggressive,ndepth, &
mycall,hiscall,hisgrid,nexp_decode,nqd,nft,qual,nhist,decoded)
mycall,hiscall,hisgrid,nQSOProgress,nexp_decode,nqd,nft,qual, &
nhist,decoded)
if(nft.eq.1) then
nsmo=ismo

View File

@ -1,5 +1,6 @@
subroutine decode65b(s2,nflip,nadd,mode65,ntrials,naggressive,ndepth, &
mycall,hiscall,hisgrid,nexp_decode,nqd,nft,qual,nhist,decoded)
mycall,hiscall,hisgrid,nQSOProgress,nexp_decode,nqd,nft,qual, &
nhist,decoded)
use jt65_mod
real s2(66,126)
@ -19,7 +20,8 @@ subroutine decode65b(s2,nflip,nadd,mode65,ntrials,naggressive,ndepth, &
enddo
call extract(s3,nadd,mode65,ntrials,naggressive,ndepth,nflip,mycall, &
hiscall,hisgrid,nexp_decode,ncount,nhist,decoded,ltext,nft,qual)
hiscall,hisgrid,nQSOProgress,nexp_decode,ncount,nhist,decoded, &
ltext,nft,qual)
! Suppress "birdie messages" and other garbage decodes:
if(decoded(1:7).eq.'000AAA ') ncount=-1

View File

@ -177,7 +177,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
logical(params%nagain),params%n2pass,logical(params%nrobust), &
ntrials,params%naggressive,params%ndepth,params%emedelay, &
logical(params%nclearave),params%mycall,params%hiscall, &
params%hisgrid,params%nexp_decode)
params%hisgrid,params%nexp_decode,params%nQSOProgress)
call timer('jt65a ',1)
else if(params%nmode.eq.9 .or. (params%nmode.eq.(65+9) .and. params%ntxmode.eq.9)) then
@ -202,7 +202,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
logical(params%nagain),params%n2pass,logical(params%nrobust), &
ntrials,params%naggressive,params%ndepth,params%emedelay, &
logical(params%nclearave),params%mycall,params%hiscall, &
params%hisgrid,params%nexp_decode)
params%hisgrid,params%nexp_decode,params%nQSOProgress)
call timer('jt65a ',1)
else
call timer('decjt9 ',0)

170
lib/fsk4hf/extract_ap.f90 Normal file
View File

@ -0,0 +1,170 @@
subroutine extract(s3,nadd,mode65,ntrials,naggressive,ndepth,nflip, &
mycall_12,hiscall_12,hisgrid,nQSOProgress,nexp_decode,ncount, &
nhist,decoded,ltext,nft,qual)
! Input:
! s3 64-point spectra for each of 63 data symbols
! nadd number of spectra summed into s3
! nqd 0/1 to indicate decode attempt at QSO frequency
! Output:
! ncount number of symbols requiring correction (-1 for no KV decode)
! nhist maximum number of identical symbol values
! decoded decoded message (if ncount >=0)
! ltext true if decoded message is free text
! nft 0=no decode; 1=FT decode; 2=hinted decode
use prog_args !shm_key, exe_dir, data_dir
use packjt
use jt65_mod
use timer_module, only: timer
real s3(64,63)
character decoded*22, apmessage*22
character*12 mycall_12,hiscall_12
character*6 mycall,hiscall,hisgrid
integer apsymbols(12)
integer dat4(12)
integer mrsym(63),mr2sym(63),mrprob(63),mr2prob(63)
integer correct(63),tmp(63)
logical ltext
common/chansyms65/correct
save
if(mode65.eq.-99) stop !Silence compiler warning
mycall=mycall_12(1:6)
hiscall=hiscall_12(1:6)
apmessage=mycall//" "//hiscall//" RRR"
call packmsg(apmessage,apsymbols,itype,.false.)
write(*,*) nQSOProgress
write(*,*) apmessage,itype
write(*,'(12i3)') apsymbols
if(itype.eq.1) then
apsymbols(10:12)=-1
else
apsymbols=-1
endif
qual=0.
nbirdie=20
npct=50
afac1=1.1
nft=0
nfail=0
decoded=' '
call pctile(s3,4032,npct,base)
s3=s3/base
s3a=s3 !###
! Get most reliable and second-most-reliable symbol values, and their
! probabilities
1 call demod64a(s3,nadd,afac1,mrsym,mrprob,mr2sym,mr2prob,ntest,nlow)
call chkhist(mrsym,nhist,ipk) !Test for birdies and QRM
if(nhist.ge.nbirdie) then
nfail=nfail+1
call pctile(s3,4032,npct,base)
s3(ipk,1:63)=base
if(nfail.gt.30) then
decoded=' '
ncount=-1
go to 900
endif
go to 1
endif
mrs=mrsym
mrs2=mr2sym
call graycode65(mrsym,63,-1) !Remove gray code
call interleave63(mrsym,-1) !Remove interleaving
call interleave63(mrprob,-1)
call graycode65(mr2sym,63,-1) !Remove gray code and interleaving
call interleave63(mr2sym,-1) !from second-most-reliable symbols
call interleave63(mr2prob,-1)
ntry=0
! call gf64_osd(s3,correct)
call timer('ftrsd ',0)
param=0
! call ftrsd2(mrsym,mrprob,mr2sym,mr2prob,ntrials,correct,param,ntry)
call ftrsdap(mrsym,mrprob,mr2sym,mr2prob,apsymbols,ntrials,correct,param,ntry)
call timer('ftrsd ',1)
ncandidates=param(0)
nhard=param(1)
nsoft=param(2)
nerased=param(3)
rtt=0.001*param(4)
ntotal=param(5)
qual=0.001*param(7)
nd0=81
r0=0.87
if(naggressive.eq.10) then
nd0=83
r0=0.90
endif
if(ntotal.le.nd0 .and. rtt.le.r0) nft=1
if(nft.eq.0 .and. iand(ndepth,32).eq.32) then
qmin=2.0 - 0.1*naggressive
call timer('hint65 ',0)
call hint65(s3,mrs,mrs2,nadd,nflip,mycall,hiscall,hisgrid,qual,decoded)
if(qual.ge.qmin) then
nft=2
ncount=0
else
decoded=' '
ntry=0
endif
call timer('hint65 ',1)
go to 900
endif
ncount=-1
decoded=' '
ltext=.false.
if(nft.gt.0) then
! Turn the corrected symbol array into channel symbols for subtraction;
! pass it back to jt65a via common block "chansyms65".
do i=1,12
dat4(i)=correct(13-i)
enddo
do i=1,63
tmp(i)=correct(64-i)
enddo
correct(1:63)=tmp(1:63)
call interleave63(correct,63,1)
call graycode65(correct,63,1)
call unpackmsg(dat4,decoded,.false.,' ') !Unpack the user message
ncount=0
if(iand(dat4(10),8).ne.0) ltext=.true.
endif
900 continue
if(nft.eq.1 .and. nhard.lt.0) decoded=' '
return
end subroutine extract
subroutine getpp(workdat,p)
use jt65_mod
integer workdat(63)
integer a(63)
a(1:63)=workdat(63:1:-1)
call interleave63(a,1)
call graycode(a,63,1,a)
psum=0.
do j=1,63
i=a(j)+1
x=s3a(i,j)
s3a(i,j)=0.
psum=psum + x
s3a(i,j)=x
enddo
p=psum/63.0
return
end subroutine getpp

View File

@ -43,6 +43,7 @@ program jt65
nhigh=4000
n2pass=1
ndepth=1
nQSOProgress=6
do
call getopt('a:d:f:hm:n:rc:x:g:X:s',long_options,c,optarg,narglen,nstat,noffset,nremain,.true.)
@ -125,7 +126,7 @@ program jt65
dd(npts+1:)=0.
call test(dd,nutc,nfa,nfb,nfqso,ntol,nsubmode, &
n2pass,nrobust,ntrials,naggressive,ndepth, &
mycall,hiscall,hisgrid,nexp_decode)
mycall,hiscall,hisgrid,nexp_decode,nQSOProgress)
! if(nft.gt.0) exit
enddo

View File

@ -37,7 +37,7 @@ contains
subroutine decode(this,callback,dd0,npts,newdat,nutc,nf1,nf2,nfqso, &
ntol,nsubmode,minsync,nagain,n2pass,nrobust,ntrials,naggressive, &
ndepth,emedelay,clearave,mycall,hiscall,hisgrid,nexp_decode)
ndepth,emedelay,clearave,mycall,hiscall,hisgrid,nexp_decode,nQSOProgress)
! Process dd0() data to find and decode JT65 signals.
@ -225,7 +225,7 @@ contains
nft=0
nspecial=0
call decode65a(dd,npts,first_time,nqd,freq,nflip,mode65,nvec, &
naggressive,ndepth,ntol,mycall,hiscall,hisgrid, &
naggressive,ndepth,ntol,mycall,hiscall,hisgrid,nQSOProgress, &
nexp_decode,bVHF,sync2,a,dtx,nft,nspecial,qual, &
nhist,nsmo,decoded)
if(nspecial.eq.2) decoded='RO'

View File

@ -11,7 +11,7 @@ module jt65_test
contains
subroutine test (dd,nutc,nflow,nfhigh,nfqso,ntol,nsubmode,n2pass,nrobust &
,ntrials,naggressive,ndepth,mycall,hiscall,hisgrid,nexp_decode)
,ntrials,naggressive,ndepth,mycall,hiscall,hisgrid,nexp_decode,nQSOProgress)
use timer_module, only: timer
use jt65_decode
implicit none
@ -19,7 +19,7 @@ contains
include 'constants.f90'
real, intent(in) :: dd(NZMAX)
integer, intent(in) :: nutc, nflow, nfhigh, nfqso, ntol, nsubmode, n2pass &
, ntrials, naggressive, ndepth, nexp_decode
, ntrials, naggressive, ndepth, nexp_decode, nQSOProgress
logical, intent(in) :: nrobust
character(len=12), intent(in) :: mycall, hiscall
character(len=6), intent(in) :: hisgrid
@ -33,7 +33,8 @@ contains
nsubmode=nsubmode, minsync=-1,nagain=.false.,n2pass=n2pass, &
nrobust=nrobust,ntrials=ntrials,naggressive=naggressive, &
ndepth=ndepth,emedelay=0.0,clearave=nclearave,mycall=mycall, &
hiscall=hiscall,hisgrid=hisgrid,nexp_decode=nexp_decode)
hiscall=hiscall,hisgrid=hisgrid,nexp_decode=nexp_decode, &
nQSOProgress=nQSOProgress)
call timer('jt65a ',1)
end subroutine test