This commit is contained in:
Steven Franke 2020-04-21 15:02:57 -05:00
parent 01d555c898
commit 8da98fee1e

View File

@ -2,127 +2,127 @@ subroutine decode174_74(llr,Keff,ndeep,apmask,maxsuper,message74,cw,nharderror,i
! !
! A hybrid bp/osd decoder for the (174,74) code. ! A hybrid bp/osd decoder for the (174,74) code.
! !
integer, parameter:: N=174, K=74, M=N-K integer, parameter:: N=174, K=74, M=N-K
integer*1 cw(N),apmask(N) integer*1 cw(N),apmask(N)
integer*1 decoded(K) integer*1 decoded(K)
integer*1 message74(74) integer*1 message74(74)
integer nrw(M),ncw integer nrw(M),ncw
integer Nm(6,M) integer Nm(6,M)
integer Mn(3,N) ! 3 checks per bit integer Mn(3,N) ! 3 checks per bit
integer synd(M) integer synd(M)
real tov(3,N) real tov(3,N)
real toc(6,M) real toc(6,M)
real tanhtoc(6,M) real tanhtoc(6,M)
real zn(N),zsum(N) real zn(N),zsum(N)
real llr(N) real llr(N)
real Tmn real Tmn
include "ldpc_174_74_parity.f90" include "ldpc_174_74_parity.f90"
decoded=0 decoded=0
toc=0 toc=0
tov=0 tov=0
tanhtoc=0 tanhtoc=0
! initialize messages to checks ! initialize messages to checks
do j=1,M do j=1,M
do i=1,nrw(j) do i=1,nrw(j)
toc(i,j)=llr((Nm(i,j))) toc(i,j)=llr((Nm(i,j)))
enddo
enddo
ncnt=0
nclast=0
maxiterations=1
zsum=0.0
do isuper=1,maxsuper
do iter=0,maxiterations
! Update bit log likelihood ratios (tov=0 in iteration 0).
do i=1,N
if( apmask(i) .ne. 1 ) then
zn(i)=llr(i)+sum(tov(1:ncw,i))
else
zn(i)=llr(i)
endif
enddo
zsum=zsum+zn
! Check to see if we have a codeword (check before we do any iteration).
cw=0
where( zn .gt. 0. ) cw=1
ncheck=0
do i=1,M
synd(i)=sum(cw(Nm(1:nrw(i),i)))
if( mod(synd(i),2) .ne. 0 ) ncheck=ncheck+1
! if( mod(synd(i),2) .ne. 0 ) write(*,*) 'check ',i,' unsatisfied'
enddo
! write(*,*) 'number of unsatisfied parity checks ',ncheck
if( ncheck .eq. 0 ) then ! we have a codeword - if crc is good, return it
decoded=cw(1:K)
call get_crc24(decoded,74,nbadcrc)
nharderror=count( (2*cw-1)*llr .lt. 0.0 )
if(nbadcrc.eq.0) then
message74=decoded(1:74)
dmin=0.0
return
endif
endif
! if( iter.gt.0 ) then ! this code block implements an early stopping criterion
if( iter.gt.10000 ) then ! this code block implements an early stopping criterion
nd=ncheck-nclast
if( nd .lt. 0 ) then ! # of unsatisfied parity checks decreased
ncnt=0 ! reset counter
else
ncnt=ncnt+1
endif
! write(*,*) iter,ncheck,nd,ncnt
if( ncnt .ge. 5 .and. iter .ge. 10 .and. ncheck .gt. 15) then
nharderror=-1
return
endif
endif
nclast=ncheck
! Send messages from bits to check nodes
do j=1,M
do i=1,nrw(j)
ibj=Nm(i,j)
toc(i,j)=zn(ibj)
do kk=1,ncw ! subtract off what the bit had received from the check
if( Mn(kk,ibj) .eq. j ) then
toc(i,j)=toc(i,j)-tov(kk,ibj)
endif
enddo enddo
enddo enddo
enddo
ncnt=0
nclast=0
maxiterations=1
zsum=0.0
do isuper=1,maxsuper
do iter=0,maxiterations
! Update bit log likelihood ratios (tov=0 in iteration 0).
do i=1,N
if( apmask(i) .ne. 1 ) then
zn(i)=llr(i)+sum(tov(1:ncw,i))
else
zn(i)=llr(i)
endif
enddo
zsum=zsum+zn
! Check to see if we have a codeword (check before we do any iteration).
cw=0
where( zn .gt. 0. ) cw=1
ncheck=0
do i=1,M
synd(i)=sum(cw(Nm(1:nrw(i),i)))
if( mod(synd(i),2) .ne. 0 ) ncheck=ncheck+1
! if( mod(synd(i),2) .ne. 0 ) write(*,*) 'check ',i,' unsatisfied'
enddo
! write(*,*) 'number of unsatisfied parity checks ',ncheck
if( ncheck .eq. 0 ) then ! we have a codeword - if crc is good, return it
decoded=cw(1:K)
call get_crc24(decoded,74,nbadcrc)
nharderror=count( (2*cw-1)*llr .lt. 0.0 )
if(nbadcrc.eq.0) then
message74=decoded(1:74)
dmin=0.0
return
endif
endif
! if( iter.gt.0 ) then ! this code block implements an early stopping criterion
if( iter.gt.10000 ) then ! this code block implements an early stopping criterion
nd=ncheck-nclast
if( nd .lt. 0 ) then ! # of unsatisfied parity checks decreased
ncnt=0 ! reset counter
else
ncnt=ncnt+1
endif
! write(*,*) iter,ncheck,nd,ncnt
if( ncnt .ge. 5 .and. iter .ge. 10 .and. ncheck .gt. 15) then
nharderror=-1
return
endif
endif
nclast=ncheck
! Send messages from bits to check nodes
do j=1,M
do i=1,nrw(j)
ibj=Nm(i,j)
toc(i,j)=zn(ibj)
do kk=1,ncw ! subtract off what the bit had received from the check
if( Mn(kk,ibj) .eq. j ) then
toc(i,j)=toc(i,j)-tov(kk,ibj)
endif
enddo
enddo
enddo
! send messages from check nodes to variable nodes ! send messages from check nodes to variable nodes
do i=1,M do i=1,M
tanhtoc(1:6,i)=tanh(-toc(1:6,i)/2) tanhtoc(1:6,i)=tanh(-toc(1:6,i)/2)
enddo enddo
do j=1,N do j=1,N
do i=1,ncw do i=1,ncw
ichk=Mn(i,j) ! Mn(:,j) are the checks that include bit j ichk=Mn(i,j) ! Mn(:,j) are the checks that include bit j
Tmn=product(tanhtoc(1:nrw(ichk),ichk),mask=Nm(1:nrw(ichk),ichk).ne.j) Tmn=product(tanhtoc(1:nrw(ichk),ichk),mask=Nm(1:nrw(ichk),ichk).ne.j)
call platanh(-Tmn,y) call platanh(-Tmn,y)
! y=atanh(-Tmn) ! y=atanh(-Tmn)
tov(i,j)=2*y tov(i,j)=2*y
enddo enddo
enddo enddo
enddo ! bp iterations enddo ! bp iterations
llr=zsum llr=zsum
call osd174_74(llr,Keff,apmask,ndeep,message74,cw,nharderror,dmin) call osd174_74(llr,Keff,apmask,ndeep,message74,cw,nharderror,dmin)
if(nharderror.gt.0) then if(nharderror.gt.0) then
return return
endif endif
enddo ! super iterations enddo ! super iterations
nharderror=-1 nharderror=-1
return return
end subroutine decode174_74 end subroutine decode174_74