Code cleanup and test ofFT8 decodes with erasures. Do not use on the air.

git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@7879 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
Joe Taylor 2017-07-14 16:02:01 +00:00
parent 230b10ab2f
commit a8cba435d4
3 changed files with 108 additions and 96 deletions

View File

@ -390,7 +390,7 @@ contains
end select end select
end subroutine jt9_decoded end subroutine jt9_decoded
subroutine ft8_decoded (this,sync,snr,dt,freq,nbadcrc,decoded) subroutine ft8_decoded (this,sync,snr,dt,freq,decoded)
use ft8_decode use ft8_decode
implicit none implicit none
@ -399,17 +399,14 @@ contains
integer, intent(in) :: snr integer, intent(in) :: snr
real, intent(in) :: dt real, intent(in) :: dt
real, intent(in) :: freq real, intent(in) :: freq
integer, intent(in) :: nbadcrc
character(len=22), intent(in) :: decoded character(len=22), intent(in) :: decoded
if(nbadcrc.eq.0) then write(*,1000) params%nutc,snr,dt,nint(freq),decoded
write(*,1000) params%nutc,snr,dt,nint(freq),decoded 1000 format(i6.6,i4,f5.1,i5,' ~ ',1x,a22)
1000 format(i6.6,i4,f5.1,i5,' ~ ',1x,a22) write(13,1002) params%nutc,nint(sync),snr,dt,freq,0,decoded
write(13,1002) params%nutc,nint(sync),snr,dt,freq,0,decoded 1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a22,' FT8')
1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a22,' FT8') call flush(6)
call flush(6) call flush(13)
call flush(13)
endif
select type(this) select type(this)
type is (counting_ft8_decoder) type is (counting_ft8_decoder)

View File

@ -1,5 +1,5 @@
subroutine ft8b(dd0,newdat,nfqso,ndepth,lsubtract,icand,sync0,f1,xdt,apsym,nharderrors, & subroutine ft8b(dd0,newdat,nfqso,ndepth,lsubtract,icand,sync0,f1,xdt, &
dmin,nbadcrc,iap,ipass,message,xsnr) apsym,nharderrors,dmin,nbadcrc,iap,ipass,iera,message,xsnr)
use timer_module, only: timer use timer_module, only: timer
include 'ft8_params.f90' include 'ft8_params.f90'
@ -9,7 +9,7 @@ subroutine ft8b(dd0,newdat,nfqso,ndepth,lsubtract,icand,sync0,f1,xdt,apsym,nhard
real a(5) real a(5)
real s1(0:7,ND),s2(0:7,NN) real s1(0:7,ND),s2(0:7,NN)
real ps(0:7) real ps(0:7)
real rxdata(3*ND),llr(3*ND),llrap(3*ND) !Soft symbols real rxdata(3*ND),llr(3*ND),llr0(3*ND),llrap(3*ND) !Soft symbols
real dd0(15*12000) real dd0(15*12000)
integer*1 decoded(KK),apmask(3*ND),cw(3*ND) integer*1 decoded(KK),apmask(3*ND),cw(3*ND)
integer*1 msgbits(KK) integer*1 msgbits(KK)
@ -109,88 +109,100 @@ subroutine ft8b(dd0,newdat,nfqso,ndepth,lsubtract,icand,sync0,f1,xdt,apsym,nhard
rxdata=rxdata/rxsig rxdata=rxdata/rxsig
ss=0.84 ss=0.84
llr=2.0*rxdata/(ss*ss) llr=2.0*rxdata/(ss*ss)
llr0=llr
apmag=4.0 apmag=4.0
! do iap=0,1 ! nera=1
nera=3
! do iap=0,3
do iap=0,0 !### Temporary ### do iap=0,0 !### Temporary ###
if(iap.eq.0) then do iera=1,nera
apmask=0 llr=llr0
apmask(160:162)=1 nblank=0
llrap=llr if(nera.eq.3 .and. iera.eq.1) nblank=48
llrap(160:162)=apmag*apsym(73:75)/ss if(nera.eq.3 .and. iera.eq.2) nblank=24
elseif(iap.eq.1) then if(nera.eq.3 .and. iera.eq.3) nblank=0
apmask=0 if(nblank.gt.0) llr(1:nblank)=0.
apmask(88:115)=1 ! mycall if(iap.eq.0) then
apmask(144)=1 ! not free text apmask=0
apmask(160:162)=1 ! 3 extra bits apmask(160:162)=1
llrap=0.0 llrap=llr
llrap(88:115)=apmag*apsym(1:28)/ss llrap(160:162)=apmag*apsym(73:75)/ss
llrap(144)=-apmag/ss elseif(iap.eq.1) then
llrap(160:162)=apmag*apsym(73:75)/ss apmask=0
where(apmask.eq.0) llrap=llr apmask(88:115)=1 ! mycall
elseif(iap.eq.2) then apmask(144)=1 ! not free text
apmask=0 apmask(160:162)=1 ! 3 extra bits
apmask(88:115)=1 ! mycall llrap=0.0
apmask(116:143)=1 ! hiscall llrap(88:115)=apmag*apsym(1:28)/ss
apmask(144)=1 ! not free text llrap(144)=-apmag/ss
apmask(160:162)=1 ! 3 extra bits llrap(160:162)=apmag*apsym(73:75)/ss
llrap=0.0 where(apmask.eq.0) llrap=llr
llrap(88:143)=apmag*apsym(1:56)/ss elseif(iap.eq.2) then
llrap(144)=-apmag/ss apmask=0
llrap(160:162)=apmag*apsym(73:75)/ss apmask(88:115)=1 ! mycall
where(apmask.eq.0) llrap=llr apmask(116:143)=1 ! hiscall
elseif(iap.eq.3) then apmask(144)=1 ! not free text
apmask=0 apmask(160:162)=1 ! 3 extra bits
apmask(88:115)=1 ! mycall llrap=0.0
apmask(116:143)=1 ! hiscall llrap(88:143)=apmag*apsym(1:56)/ss
apmask(144:154)=1 ! RRR or 73 llrap(144)=-apmag/ss
apmask(160:162)=1 ! 3 extra bits llrap(160:162)=apmag*apsym(73:75)/ss
llrap=0.0 where(apmask.eq.0) llrap=llr
llrap(88:143)=apmag*apsym(1:56)/ss elseif(iap.eq.3) then
llrap(144:154)=apmag*rr73/ss apmask=0
llrap(160:162)=apmag*apsym(73:75)/ss apmask(88:115)=1 ! mycall
where(apmask.eq.0) llrap=llr apmask(116:143)=1 ! hiscall
endif apmask(144:154)=1 ! RRR or 73
cw=0 apmask(160:162)=1 ! 3 extra bits
call timer('bpd174 ',0) llrap=0.0
call bpdecode174(llrap,apmask,max_iterations,decoded,cw,nharderrors,niterations) llrap(88:143)=apmag*apsym(1:56)/ss
call timer('bpd174 ',1) llrap(144:154)=apmag*rr73/ss
dmin=0.0 llrap(160:162)=apmag*apsym(73:75)/ss
if(ndepth.eq.3 .and. abs(nfqso-f1).lt.10.0 .and. nharderrors.lt.0) then where(apmask.eq.0) llrap=llr
call timer('osd174 ',0) endif
call osd174(llrap,apmask,norder,decoded,cw,nharderrors,dmin) cw=0
call timer('osd174 ',1) call timer('bpd174 ',0)
endif call bpdecode174(llrap,apmask,max_iterations,decoded,cw,nharderrors, &
nbadcrc=1 niterations)
message=' ' call timer('bpd174 ',1)
xsnr=-99.0 dmin=0.0
if(count(cw.eq.0).eq.174) cycle !Reject the all-zero codeword if(ndepth.eq.3 .and. abs(nfqso-f1).lt.10.0 .and. nharderrors.lt.0) then
call timer('osd174 ',0)
call osd174(llrap,apmask,norder,decoded,cw,nharderrors,dmin)
call timer('osd174 ',1)
endif
nbadcrc=1
message=' '
xsnr=-99.0
if(count(cw.eq.0).eq.174) cycle !Reject the all-zero codeword
! if( nharderrors.ge.0 .and. dmin.le.30.0 .and. nharderrors .lt. 30) then ! if( nharderrors.ge.0 .and. dmin.le.30.0 .and. nharderrors .lt. 30) then
!*** These thresholds should probably be dependent on nap !*** These thresholds should probably be dependent on nap
if( nharderrors.ge.0 .and. dmin.le.50.0 .and. nharderrors .lt. 50) then if( nharderrors.ge.0 .and. dmin.le.50.0 .and. nharderrors .lt. 50) then
call chkcrc12a(decoded,nbadcrc) call chkcrc12a(decoded,nbadcrc)
else else
nharderrors=-1 nharderrors=-1
cycle cycle
endif endif
if(nbadcrc.eq.0) then if(nbadcrc.eq.0) then
call extractmessage174(decoded,message,ncrcflag,recent_calls,nrecent) call extractmessage174(decoded,message,ncrcflag,recent_calls,nrecent)
call genft8(message,msgsent,msgbits,itone) call genft8(message,msgsent,msgbits,itone)
if(lsubtract) call subtractft8(dd0,itone,f1,xdt2) if(lsubtract) call subtractft8(dd0,itone,f1,xdt2)
xsig=0.0 xsig=0.0
xnoi=0.0 xnoi=0.0
do i=1,79 do i=1,79
xsig=xsig+s2(itone(i),i)**2 xsig=xsig+s2(itone(i),i)**2
ios=mod(itone(i)+4,7) ios=mod(itone(i)+4,7)
xnoi=xnoi+s2(ios,i)**2 xnoi=xnoi+s2(ios,i)**2
enddo
xsnr=0.001
if(xnoi.gt.0 .and. xnoi.lt.xsig) xsnr=xsig/xnoi-1.0
xsnr=10.0*log10(xsnr)-27.0
if(xsnr .lt. -24.0) xsnr=-24.0
exit
endif
enddo enddo
xsnr=0.001
if( xnoi.gt.0 .and. xnoi.lt.xsig ) xsnr=xsig/xnoi-1.0
xsnr=10.0*log10(xsnr)-27.0
if( xsnr .lt. -24.0 ) xsnr=-24.0
! write(50,3050) icand,sync0,f1,xdt,xsnr,nharderrors,niterations,dmin,iap,ipass,message
!3050 format(i3,4f10.3,i5,i5,f10.3,i4,i4,2x,a22)
return
endif
enddo enddo
return return
end subroutine ft8b end subroutine ft8b

View File

@ -7,7 +7,7 @@ module ft8_decode
end type ft8_decoder end type ft8_decoder
abstract interface abstract interface
subroutine ft8_decode_callback (this,sync,snr,dt,freq,nbadcrc,decoded) subroutine ft8_decode_callback (this,sync,snr,dt,freq,decoded)
import ft8_decoder import ft8_decoder
implicit none implicit none
class(ft8_decoder), intent(inout) :: this class(ft8_decoder), intent(inout) :: this
@ -15,7 +15,6 @@ module ft8_decode
integer, intent(in) :: snr integer, intent(in) :: snr
real, intent(in) :: dt real, intent(in) :: dt
real, intent(in) :: freq real, intent(in) :: freq
integer, intent(in) :: nbadcrc
character(len=22), intent(in) :: decoded character(len=22), intent(in) :: decoded
end subroutine ft8_decode_callback end subroutine ft8_decode_callback
end interface end interface
@ -77,13 +76,17 @@ contains
xdt=candidate(2,icand) xdt=candidate(2,icand)
nsnr0=min(99,nint(10.0*log10(sync) - 25.5)) !### empirical ### nsnr0=min(99,nint(10.0*log10(sync) - 25.5)) !### empirical ###
call timer('ft8b ',0) call timer('ft8b ',0)
call ft8b(dd,newdat,nfqso,ndepth,lsubtract,icand,sync,f1,xdt,apsym,nharderrors, & call ft8b(dd,newdat,nfqso,ndepth,lsubtract,icand,sync,f1,xdt, &
dmin,nbadcrc,iap,ipass,message,xsnr) apsym,nharderrors,dmin,nbadcrc,iap,ipass,iera,message,xsnr)
nsnr=xsnr nsnr=xsnr
xdt=xdt-0.6 xdt=xdt-0.6
call timer('ft8b ',1) call timer('ft8b ',1)
if (associated(this%callback)) call this%callback(sync,nsnr,xdt, & if(nbadcrc.eq.0 .and. associated(this%callback)) then
f1,nbadcrc,message) call this%callback(sync,nsnr,xdt,f1,message)
write(81,3081) ncand,icand,iera,nharderrors,ipass, &
sync,f1,xdt,dmin,xsnr,message
3081 format(2i5,i2,i3,i2,2f7.1,3f7.2,1x,a22)
endif
enddo enddo
! h=default_header(12000,NMAX) ! h=default_header(12000,NMAX)
! open(10,file='subtract.wav',status='unknown',access='stream') ! open(10,file='subtract.wav',status='unknown',access='stream')