mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2024-11-04 16:31:17 -05:00
Add fst280 files.
This commit is contained in:
parent
7478978305
commit
a720e0ec21
111
lib/fst280/bpdecode280_101.f90
Normal file
111
lib/fst280/bpdecode280_101.f90
Normal file
@ -0,0 +1,111 @@
|
|||||||
|
subroutine bpdecode280_101(llr,apmask,maxiterations,message101,cw,nharderror,iter,ncheck)
|
||||||
|
!
|
||||||
|
! A log-domain belief propagation decoder for the (280,101) code.
|
||||||
|
!
|
||||||
|
integer, parameter:: N=280, K=101, M=N-K
|
||||||
|
integer*1 cw(N),apmask(N)
|
||||||
|
integer*1 decoded(K)
|
||||||
|
integer*1 message101(101)
|
||||||
|
integer nrw(M),ncw
|
||||||
|
integer Nm(6,M)
|
||||||
|
integer Mn(3,N) ! 3 checks per bit
|
||||||
|
integer synd(M)
|
||||||
|
real tov(3,N)
|
||||||
|
real toc(6,M)
|
||||||
|
real tanhtoc(6,M)
|
||||||
|
real zn(N)
|
||||||
|
real llr(N)
|
||||||
|
real Tmn
|
||||||
|
|
||||||
|
include "ldpc_280_101_parity.f90"
|
||||||
|
|
||||||
|
decoded=0
|
||||||
|
toc=0
|
||||||
|
tov=0
|
||||||
|
tanhtoc=0
|
||||||
|
! initialize messages to checks
|
||||||
|
do j=1,M
|
||||||
|
do i=1,nrw(j)
|
||||||
|
toc(i,j)=llr((Nm(i,j)))
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ncnt=0
|
||||||
|
nclast=0
|
||||||
|
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
|
||||||
|
|
||||||
|
! 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
|
||||||
|
if( ncheck .eq. 0 ) then ! we have a codeword - if crc is good, return it
|
||||||
|
decoded=cw(1:101)
|
||||||
|
call get_crc24(decoded,101,nbadcrc)
|
||||||
|
nharderror=count( (2*cw-1)*llr .lt. 0.0 )
|
||||||
|
if(nbadcrc.eq.0) then
|
||||||
|
message101=decoded(1:101)
|
||||||
|
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
|
||||||
|
do i=1,M
|
||||||
|
tanhtoc(1:6,i)=tanh(-toc(1:6,i)/2)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
do j=1,N
|
||||||
|
do i=1,ncw
|
||||||
|
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)
|
||||||
|
call platanh(-Tmn,y)
|
||||||
|
! y=atanh(-Tmn)
|
||||||
|
tov(i,j)=2*y
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
enddo
|
||||||
|
nharderror=-1
|
||||||
|
return
|
||||||
|
end subroutine bpdecode280_101
|
111
lib/fst280/bpdecode280_74.f90
Normal file
111
lib/fst280/bpdecode280_74.f90
Normal file
@ -0,0 +1,111 @@
|
|||||||
|
subroutine bpdecode280_74(llr,apmask,maxiterations,message74,cw,nharderror,iter,ncheck)
|
||||||
|
!
|
||||||
|
! A log-domain belief propagation decoder for the (280,74) code.
|
||||||
|
!
|
||||||
|
integer, parameter:: N=280, K=74, M=N-K
|
||||||
|
integer*1 cw(N),apmask(N)
|
||||||
|
integer*1 decoded(K)
|
||||||
|
integer*1 message74(74)
|
||||||
|
integer nrw(M),ncw
|
||||||
|
integer Nm(5,M)
|
||||||
|
integer Mn(3,N) ! 3 checks per bit
|
||||||
|
integer synd(M)
|
||||||
|
real tov(3,N)
|
||||||
|
real toc(5,M)
|
||||||
|
real tanhtoc(5,M)
|
||||||
|
real zn(N)
|
||||||
|
real llr(N)
|
||||||
|
real Tmn
|
||||||
|
|
||||||
|
include "ldpc_280_74_parity.f90"
|
||||||
|
|
||||||
|
decoded=0
|
||||||
|
toc=0
|
||||||
|
tov=0
|
||||||
|
tanhtoc=0
|
||||||
|
! initialize messages to checks
|
||||||
|
do j=1,M
|
||||||
|
do i=1,nrw(j)
|
||||||
|
toc(i,j)=llr((Nm(i,j)))
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ncnt=0
|
||||||
|
nclast=0
|
||||||
|
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
|
||||||
|
|
||||||
|
! 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
|
||||||
|
if( ncheck .eq. 0 ) then ! we have a codeword - if crc is good, return it
|
||||||
|
decoded=cw(1:74)
|
||||||
|
call get_crc24(decoded,74,nbadcrc)
|
||||||
|
nharderror=count( (2*cw-1)*llr .lt. 0.0 )
|
||||||
|
if(nbadcrc.eq.0) then
|
||||||
|
message74=decoded(1:74)
|
||||||
|
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
|
||||||
|
do i=1,M
|
||||||
|
tanhtoc(1:5,i)=tanh(-toc(1:5,i)/2)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
do j=1,N
|
||||||
|
do i=1,ncw
|
||||||
|
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)
|
||||||
|
call platanh(-Tmn,y)
|
||||||
|
! y=atanh(-Tmn)
|
||||||
|
tov(i,j)=2*y
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
enddo
|
||||||
|
nharderror=-1
|
||||||
|
return
|
||||||
|
end subroutine bpdecode280_74
|
154
lib/fst280/decode280_101.f90
Normal file
154
lib/fst280/decode280_101.f90
Normal file
@ -0,0 +1,154 @@
|
|||||||
|
subroutine decode280_101(llr,Keff,maxosd,norder,apmask,message101,cw,ntype,nharderror,dmin)
|
||||||
|
!
|
||||||
|
! A hybrid bp/osd decoder for the (280,101) code.
|
||||||
|
!
|
||||||
|
! maxosd<0: do bp only
|
||||||
|
! maxosd=0: do bp and then call osd once with channel llrs
|
||||||
|
! maxosd>1: do bp and then call osd maxosd times with saved bp outputs
|
||||||
|
! norder : osd decoding depth
|
||||||
|
!
|
||||||
|
integer, parameter:: N=280, K=101, M=N-K
|
||||||
|
integer*1 cw(N),apmask(N)
|
||||||
|
integer*1 nxor(N),hdec(N)
|
||||||
|
integer*1 message101(101),m101(101)
|
||||||
|
integer nrw(M),ncw
|
||||||
|
integer Nm(6,M)
|
||||||
|
integer Mn(3,N) ! 3 checks per bit
|
||||||
|
integer synd(M)
|
||||||
|
real tov(3,N)
|
||||||
|
real toc(6,M)
|
||||||
|
real tanhtoc(6,M)
|
||||||
|
real zn(N),zsum(N),zsave(N,3)
|
||||||
|
real llr(N)
|
||||||
|
real Tmn
|
||||||
|
|
||||||
|
include "ldpc_280_101_parity.f90"
|
||||||
|
|
||||||
|
maxiterations=30
|
||||||
|
nosd=0
|
||||||
|
if(maxosd.gt.3) maxosd=3
|
||||||
|
if(maxosd.eq.0) then ! osd with channel llrs
|
||||||
|
nosd=1
|
||||||
|
zsave(:,1)=llr
|
||||||
|
elseif(maxosd.gt.0) then !
|
||||||
|
nosd=maxosd
|
||||||
|
elseif(maxosd.lt.0) then ! just bp
|
||||||
|
nosd=0
|
||||||
|
endif
|
||||||
|
|
||||||
|
toc=0
|
||||||
|
tov=0
|
||||||
|
tanhtoc=0
|
||||||
|
! initialize messages to checks
|
||||||
|
do j=1,M
|
||||||
|
do i=1,nrw(j)
|
||||||
|
toc(i,j)=llr((Nm(i,j)))
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ncnt=0
|
||||||
|
nclast=0
|
||||||
|
zsum=0.0
|
||||||
|
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
|
||||||
|
if(iter.gt.0 .and. iter.le.maxosd) then
|
||||||
|
zsave(:,iter)=zsum
|
||||||
|
endif
|
||||||
|
|
||||||
|
! 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
|
||||||
|
enddo
|
||||||
|
if( ncheck .eq. 0 ) then ! we have a codeword - if crc is good, return it
|
||||||
|
m101=0
|
||||||
|
m101(1:101)=cw(1:101)
|
||||||
|
call get_crc24(m101,101,nbadcrc)
|
||||||
|
if(nbadcrc.eq.0) then
|
||||||
|
message101=cw(1:101)
|
||||||
|
hdec=0
|
||||||
|
where(llr .ge. 0) hdec=1
|
||||||
|
nxor=ieor(hdec,cw)
|
||||||
|
nharderror=sum(nxor)
|
||||||
|
dmin=sum(nxor*abs(llr))
|
||||||
|
ntype=1
|
||||||
|
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
|
||||||
|
exit
|
||||||
|
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
|
||||||
|
do i=1,M
|
||||||
|
tanhtoc(1:6,i)=tanh(-toc(1:6,i)/2)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
do j=1,N
|
||||||
|
do i=1,ncw
|
||||||
|
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)
|
||||||
|
call platanh(-Tmn,y)
|
||||||
|
! y=atanh(-Tmn)
|
||||||
|
tov(i,j)=2*y
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
enddo ! bp iterations
|
||||||
|
|
||||||
|
do i=1,nosd
|
||||||
|
zn=zsave(:,i)
|
||||||
|
call osd280_101(zn,Keff,apmask,norder,message101,cw,nharderror,dminosd)
|
||||||
|
if(nharderror.gt.0) then
|
||||||
|
hdec=0
|
||||||
|
where(llr .ge. 0) hdec=1
|
||||||
|
nxor=ieor(hdec,cw)
|
||||||
|
dmin=sum(nxor*abs(llr))
|
||||||
|
ntype=2
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ntype=0
|
||||||
|
nharderror=-1
|
||||||
|
dminosd=0.0
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine decode280_101
|
153
lib/fst280/decode280_74.f90
Normal file
153
lib/fst280/decode280_74.f90
Normal file
@ -0,0 +1,153 @@
|
|||||||
|
subroutine decode280_74(llr,Keff,maxosd,norder,apmask,message74,cw,ntype,nharderror,dmin)
|
||||||
|
!
|
||||||
|
! A hybrid bp/osd decoder for the (280,74) code.
|
||||||
|
!
|
||||||
|
! maxosd<0: do bp only
|
||||||
|
! maxosd=0: do bp and then call osd once with channel llrs
|
||||||
|
! maxosd>1: do bp and then call osd maxosd times with saved bp outputs
|
||||||
|
! norder : osd decoding depth
|
||||||
|
!
|
||||||
|
integer, parameter:: N=280, K=74, M=N-K
|
||||||
|
integer*1 cw(N),cwbest(N),apmask(N)
|
||||||
|
integer*1 nxor(N),hdec(N)
|
||||||
|
integer*1 message74(74),m74(74)
|
||||||
|
integer nrw(M),ncw
|
||||||
|
integer Nm(5,M)
|
||||||
|
integer Mn(3,N) ! 3 checks per bit
|
||||||
|
integer synd(M)
|
||||||
|
real tov(3,N)
|
||||||
|
real toc(5,M)
|
||||||
|
real tanhtoc(5,M)
|
||||||
|
real zn(N),zsum(N),zsave(N,max(1,maxosd))
|
||||||
|
real llr(N)
|
||||||
|
real Tmn
|
||||||
|
|
||||||
|
include "ldpc_280_74_parity.f90"
|
||||||
|
|
||||||
|
maxiterations=30
|
||||||
|
nosd=0
|
||||||
|
if(maxosd.eq.0) then ! osd with channel llrs
|
||||||
|
nosd=1
|
||||||
|
zsave(:,1)=llr
|
||||||
|
elseif(maxosd.gt.0) then !
|
||||||
|
nosd=maxosd
|
||||||
|
elseif(maxosd.lt.0) then ! just bp
|
||||||
|
nosd=0
|
||||||
|
endif
|
||||||
|
|
||||||
|
toc=0
|
||||||
|
tov=0
|
||||||
|
tanhtoc=0
|
||||||
|
! initialize messages to checks
|
||||||
|
do j=1,M
|
||||||
|
do i=1,nrw(j)
|
||||||
|
toc(i,j)=llr((Nm(i,j)))
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ncnt=0
|
||||||
|
nclast=0
|
||||||
|
zsum=0.0
|
||||||
|
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
|
||||||
|
if(iter.gt.0 .and. iter.le.maxosd) then
|
||||||
|
zsave(:,iter)=zsum
|
||||||
|
endif
|
||||||
|
|
||||||
|
! 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
|
||||||
|
enddo
|
||||||
|
if( ncheck .eq. 0 ) then ! we have a codeword - if crc is good, return it
|
||||||
|
m74=0
|
||||||
|
m74(1:74)=cw(1:74)
|
||||||
|
call get_crc24(m74,74,nbadcrc)
|
||||||
|
if(nbadcrc.eq.0) then
|
||||||
|
message74=cw(1:74)
|
||||||
|
hdec=0
|
||||||
|
where(llr .ge. 0) hdec=1
|
||||||
|
nxor=ieor(hdec,cw)
|
||||||
|
nharderror=sum(nxor)
|
||||||
|
dmin=sum(nxor*abs(llr))
|
||||||
|
ntype=1
|
||||||
|
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
|
||||||
|
exit
|
||||||
|
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
|
||||||
|
do i=1,M
|
||||||
|
tanhtoc(1:5,i)=tanh(-toc(1:5,i)/2)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
do j=1,N
|
||||||
|
do i=1,ncw
|
||||||
|
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)
|
||||||
|
call platanh(-Tmn,y)
|
||||||
|
! y=atanh(-Tmn)
|
||||||
|
tov(i,j)=2*y
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
enddo ! bp iterations
|
||||||
|
|
||||||
|
do i=1,nosd
|
||||||
|
zn=zsave(:,i)
|
||||||
|
call osd280_74(zn,Keff,apmask,norder,message74,cw,nharderror,dminosd)
|
||||||
|
if(nharderror.ge.0) then
|
||||||
|
hdec=0
|
||||||
|
where(llr .ge. 0) hdec=1
|
||||||
|
nxor=ieor(hdec,cw)
|
||||||
|
dmin=sum(nxor*abs(llr))
|
||||||
|
ntype=2
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ntype=0
|
||||||
|
nharderror=-1
|
||||||
|
dminosd=0.0
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine decode280_74
|
46
lib/fst280/encode280_101.f90
Normal file
46
lib/fst280/encode280_101.f90
Normal file
@ -0,0 +1,46 @@
|
|||||||
|
subroutine encode280_101(message,codeword)
|
||||||
|
use, intrinsic :: iso_c_binding
|
||||||
|
use iso_c_binding, only: c_loc,c_size_t
|
||||||
|
use crc
|
||||||
|
|
||||||
|
integer, parameter:: N=280, K=101, M=N-K
|
||||||
|
character*24 c24
|
||||||
|
integer*1 codeword(N)
|
||||||
|
integer*1 gen(M,K)
|
||||||
|
integer*1 message(K)
|
||||||
|
integer*1 pchecks(M)
|
||||||
|
integer*4 ncrc24
|
||||||
|
include "ldpc_280_101_generator.f90"
|
||||||
|
logical first
|
||||||
|
data first/.true./
|
||||||
|
save first,gen
|
||||||
|
|
||||||
|
if( first ) then ! fill the generator matrix
|
||||||
|
gen=0
|
||||||
|
do i=1,M
|
||||||
|
do j=1,26
|
||||||
|
read(g(i)(j:j),"(Z1)") istr
|
||||||
|
ibmax=4
|
||||||
|
if(j.eq.26) ibmax=1
|
||||||
|
do jj=1, ibmax
|
||||||
|
icol=(j-1)*4+jj
|
||||||
|
if( btest(istr,4-jj) ) gen(i,icol)=1
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
first=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
do i=1,M
|
||||||
|
nsum=0
|
||||||
|
do j=1,K
|
||||||
|
nsum=nsum+message(j)*gen(i,j)
|
||||||
|
enddo
|
||||||
|
pchecks(i)=mod(nsum,2)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
codeword(1:K)=message
|
||||||
|
codeword(K+1:N)=pchecks
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine encode280_101
|
46
lib/fst280/encode280_74.f90
Normal file
46
lib/fst280/encode280_74.f90
Normal file
@ -0,0 +1,46 @@
|
|||||||
|
subroutine encode280_74(message,codeword)
|
||||||
|
use, intrinsic :: iso_c_binding
|
||||||
|
use iso_c_binding, only: c_loc,c_size_t
|
||||||
|
use crc
|
||||||
|
|
||||||
|
integer, parameter:: N=280, K=74, M=N-K
|
||||||
|
character*24 c24
|
||||||
|
integer*1 codeword(N)
|
||||||
|
integer*1 gen(M,K)
|
||||||
|
integer*1 message(K)
|
||||||
|
integer*1 pchecks(M)
|
||||||
|
integer*4 ncrc24
|
||||||
|
include "ldpc_280_74_generator.f90"
|
||||||
|
logical first
|
||||||
|
data first/.true./
|
||||||
|
save first,gen
|
||||||
|
|
||||||
|
if( first ) then ! fill the generator matrix
|
||||||
|
gen=0
|
||||||
|
do i=1,M
|
||||||
|
do j=1,19
|
||||||
|
read(g(i)(j:j),"(Z1)") istr
|
||||||
|
ibmax=4
|
||||||
|
if(j.eq.19) ibmax=2
|
||||||
|
do jj=1, ibmax
|
||||||
|
icol=(j-1)*4+jj
|
||||||
|
if( btest(istr,4-jj) ) gen(i,icol)=1
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
first=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
do i=1,M
|
||||||
|
nsum=0
|
||||||
|
do j=1,K
|
||||||
|
nsum=nsum+message(j)*gen(i,j)
|
||||||
|
enddo
|
||||||
|
pchecks(i)=mod(nsum,2)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
codeword(1:K)=message
|
||||||
|
codeword(K+1:N)=pchecks
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine encode280_74
|
10
lib/fst280/fst280.txt
Normal file
10
lib/fst280/fst280.txt
Normal file
@ -0,0 +1,10 @@
|
|||||||
|
-------------------------------------------------------------------
|
||||||
|
NSPS T/R TxT Tst Txtra Txtra-2.6s DF BW SNR77 SNR50
|
||||||
|
(s) (s) (s) (s) (s) (Hz) (Hz) (dB) (dB)
|
||||||
|
-------------------------------------------------------------------
|
||||||
|
800 15 10.93 0.5 3.57 0.97 15.00 60.0 -21.3 -23.2
|
||||||
|
1680 30 22.96 1.0 6.04 3.44 7.14 28.6 -24.5 -26.4
|
||||||
|
4000 60 54.67 1.0 4.33 1.73 3.00 12.0 -28.3 -30.2
|
||||||
|
8400 120 114.80 1.0 4.20 1.60 1.43 5.7 -31.5 -33.4
|
||||||
|
21504 300 293.89 1.0 5.11 2.51 0.56 2.2 -35.5 -37.4
|
||||||
|
-------------------------------------------------------------------
|
477
lib/fst280/fst280d.f90
Normal file
477
lib/fst280/fst280d.f90
Normal file
@ -0,0 +1,477 @@
|
|||||||
|
program fst280d
|
||||||
|
|
||||||
|
! Decode fst280 data read from *.c2 or *.wav files.
|
||||||
|
|
||||||
|
use packjt77
|
||||||
|
include 'ft4s280_params.f90'
|
||||||
|
character arg*8,infile*80,fname*16,datetime*11
|
||||||
|
! character ch1*1,ch4*4,cseq*31
|
||||||
|
! character*22 decodes(100)
|
||||||
|
character*37 msg
|
||||||
|
character*120 data_dir
|
||||||
|
character*77 c77
|
||||||
|
character*1 tr_designator
|
||||||
|
complex, allocatable :: c2(:)
|
||||||
|
complex, allocatable :: cframe(:)
|
||||||
|
complex, allocatable :: c_bigfft(:) !Complex waveform
|
||||||
|
real, allocatable :: r_data(:)
|
||||||
|
real*8 fMHz
|
||||||
|
real llr(280),llra(280),llrb(280),llrc(280),llrd(280)
|
||||||
|
real candidates(100,3)
|
||||||
|
real bitmetrics(328,4)
|
||||||
|
integer ihdr(11)
|
||||||
|
integer*2, allocatable :: iwave(:)
|
||||||
|
integer*1 apmask(280),cw(280)
|
||||||
|
integer*1 hbits(328)
|
||||||
|
integer*1 message101(101),message74(74)
|
||||||
|
logical badsync,unpk77_success
|
||||||
|
|
||||||
|
hmod=1.0
|
||||||
|
Keff=91
|
||||||
|
ndeep=3
|
||||||
|
iwspr=0
|
||||||
|
|
||||||
|
nargs=iargc()
|
||||||
|
if(nargs.lt.1) then
|
||||||
|
print*,'Usage: fst280d [-a <data_dir>] [-f fMHz] [-h hmod] [-k Keff] file1 [file2 ...]'
|
||||||
|
go to 999
|
||||||
|
endif
|
||||||
|
iarg=1
|
||||||
|
data_dir="."
|
||||||
|
call getarg(iarg,arg)
|
||||||
|
if(arg(1:2).eq.'-a') then
|
||||||
|
call getarg(iarg+1,data_dir)
|
||||||
|
iarg=iarg+2
|
||||||
|
call getarg(iarg,arg)
|
||||||
|
endif
|
||||||
|
if(arg(1:2).eq.'-f') then
|
||||||
|
call getarg(iarg+1,arg)
|
||||||
|
read(arg,*) fMHz
|
||||||
|
iarg=iarg+2
|
||||||
|
call getarg(iarg,arg)
|
||||||
|
endif
|
||||||
|
if(arg(1:2).eq.'-h') then
|
||||||
|
call getarg(iarg+1,arg)
|
||||||
|
read(arg,*) hmod
|
||||||
|
if(hmod.ne.1.and.hmod.ne.2.and.hmod.ne.4) then
|
||||||
|
print*,'invalid modulation index. h must be 1, 2, or 4'
|
||||||
|
goto 999
|
||||||
|
endif
|
||||||
|
iarg=iarg+2
|
||||||
|
call getarg(iarg,arg)
|
||||||
|
endif
|
||||||
|
if(arg(1:2).eq.'-k') then
|
||||||
|
call getarg(iarg+1,arg)
|
||||||
|
read(arg,*) Keff
|
||||||
|
if(Keff.le.74) iwspr=1
|
||||||
|
iarg=iarg+2
|
||||||
|
call getarg(iarg,arg)
|
||||||
|
endif
|
||||||
|
if(arg(1:2).eq.'-d') then
|
||||||
|
call getarg(iarg+1,arg)
|
||||||
|
read(arg,*) ndeep
|
||||||
|
iarg=iarg+2
|
||||||
|
call getarg(iarg,arg)
|
||||||
|
endif
|
||||||
|
if(arg(1:2).eq.'-t') then
|
||||||
|
call getarg(iarg+1,arg)
|
||||||
|
read(arg,*) tr_designator
|
||||||
|
iarg=iarg+2
|
||||||
|
endif
|
||||||
|
|
||||||
|
nmax=15*12000
|
||||||
|
select case (tr_designator)
|
||||||
|
case('A')
|
||||||
|
nsps=800
|
||||||
|
nmax=15*12000
|
||||||
|
ndown=32/hmod
|
||||||
|
case('B')
|
||||||
|
nsps=1680
|
||||||
|
nmax=30*12000
|
||||||
|
ndown=70/hmod
|
||||||
|
if(hmod.eq.4) ndown=15
|
||||||
|
case('C')
|
||||||
|
nsps=4000
|
||||||
|
nmax=60*12000
|
||||||
|
ndown=160/hmod
|
||||||
|
case('D')
|
||||||
|
nsps=8400
|
||||||
|
nmax=120*12000
|
||||||
|
ndown=350/hmod
|
||||||
|
if(hmod.eq.4) ndown=84
|
||||||
|
case('E')
|
||||||
|
nsps=21504
|
||||||
|
nmax=300*12000
|
||||||
|
ndown=896/hmod
|
||||||
|
end select
|
||||||
|
nss=nsps/ndown
|
||||||
|
fs=12000.0 !Sample rate
|
||||||
|
fs2=fs/ndown
|
||||||
|
nspsec=nint(fs2)
|
||||||
|
dt=1.0/fs !Sample interval (s)
|
||||||
|
dt2=1.0/fs2
|
||||||
|
tt=nsps*dt !Duration of "itone" symbols (s)
|
||||||
|
|
||||||
|
nfft1=2*int(nmax/2)
|
||||||
|
nh1=nfft1/2
|
||||||
|
allocate( r_data(1:nfft1+2) )
|
||||||
|
allocate( c_bigfft(0:nfft1/2) )
|
||||||
|
|
||||||
|
nfft2=nfft1/ndown
|
||||||
|
allocate( c2(0:nfft2-1) )
|
||||||
|
allocate( cframe(0:164*nss-1) )
|
||||||
|
allocate( iwave(nmax) )
|
||||||
|
|
||||||
|
!write(*,*) 'nsps: ',nsps
|
||||||
|
!write(*,*) 'nmax: ',nmax
|
||||||
|
!write(*,*) 'nss : ',nss
|
||||||
|
!write(*,*) 'nspsec: ',fs2
|
||||||
|
!write(*,*) 'nfft1 : ',nfft1
|
||||||
|
!write(*,*) 'nfft2 : ',nfft2
|
||||||
|
|
||||||
|
ngood=0
|
||||||
|
ngoodsync=0
|
||||||
|
nfile=0
|
||||||
|
do ifile=iarg,nargs
|
||||||
|
nfile=nfile+1
|
||||||
|
call getarg(ifile,infile)
|
||||||
|
open(10,file=infile,status='old',access='stream')
|
||||||
|
j1=index(infile,'.c2')
|
||||||
|
j2=index(infile,'.wav')
|
||||||
|
if(j1.gt.0) then
|
||||||
|
read(10,end=999) fname,ntrmin,fMHz,c2
|
||||||
|
read(fname(8:11),*) nutc
|
||||||
|
write(datetime,'(i11)') nutc
|
||||||
|
else if(j2.gt.0) then
|
||||||
|
read(10,end=999) ihdr,iwave
|
||||||
|
read(infile(j2-4:j2-1),*) nutc
|
||||||
|
datetime=infile(j2-11:j2-1)
|
||||||
|
else
|
||||||
|
print*,'Wrong file format?'
|
||||||
|
go to 999
|
||||||
|
endif
|
||||||
|
close(10)
|
||||||
|
|
||||||
|
npts=nmax
|
||||||
|
fa=100.0
|
||||||
|
fb=3500.0
|
||||||
|
|
||||||
|
! The big fft is done once and is used for calculating the smoothed spectrum
|
||||||
|
! and also for downconverting/downsampling each candidate.
|
||||||
|
r_data(1:nfft1)=iwave(1:nfft1)
|
||||||
|
r_data(nfft1+1:nfft1+2)=0.0
|
||||||
|
call four2a(r_data,nfft1,1,-1,0)
|
||||||
|
c_bigfft=cmplx(r_data(1:nfft1+2:2),r_data(2:nfft1+2:2))
|
||||||
|
|
||||||
|
! Get first approximation of candidate frequencies
|
||||||
|
call get_candidates_fst280(c_bigfft,nfft1,nsps,hmod,fs,fa,fb,ncand,candidates)
|
||||||
|
|
||||||
|
ndecodes=0
|
||||||
|
isbest1=0
|
||||||
|
isbest8=0
|
||||||
|
fc21=fc0
|
||||||
|
fc28=fc0
|
||||||
|
do icand=1,ncand
|
||||||
|
fc0=candidates(icand,1)
|
||||||
|
xsnr=candidates(icand,2)
|
||||||
|
|
||||||
|
! Downconvert and downsample a slice of the spectrum centered on the
|
||||||
|
! rough estimate of the candidates frequency.
|
||||||
|
! Output array c2 is complex baseband sampled at 12000/ndown Sa/sec.
|
||||||
|
! The size of the downsampled c2 array is nfft2=nfft1/ndown
|
||||||
|
|
||||||
|
call fst280_downsample(c_bigfft,nfft1,ndown,fc0,c2)
|
||||||
|
! write(*,3001) c2(nfft2/3),candidates(icand,1:2)
|
||||||
|
!3001 format(2e15.6,2f10.3)
|
||||||
|
|
||||||
|
do isync=0,1
|
||||||
|
if(isync.eq.0) then
|
||||||
|
fc1=0.0
|
||||||
|
is0=nint(fs2)
|
||||||
|
ishw=is0
|
||||||
|
isst=4
|
||||||
|
ifhw=10
|
||||||
|
df=.1*8400/nsps
|
||||||
|
else if(isync.eq.1) then
|
||||||
|
fc1=fc28
|
||||||
|
is0=isbest8
|
||||||
|
ishw=4
|
||||||
|
isst=1
|
||||||
|
ifhw=10
|
||||||
|
df=.02*8400/nsps
|
||||||
|
endif
|
||||||
|
|
||||||
|
smax1=0.0
|
||||||
|
smax8=0.0
|
||||||
|
do if=-ifhw,ifhw
|
||||||
|
fc=fc1+df*if
|
||||||
|
do istart=max(1,is0-ishw),is0+ishw,isst
|
||||||
|
call sync_fst280(c2,istart,fc,hmod,1,nfft2,nss,fs2,sync1)
|
||||||
|
call sync_fst280(c2,istart,fc,hmod,8,nfft2,nss,fs2,sync8)
|
||||||
|
if(sync8.gt.smax8) then
|
||||||
|
fc28=fc
|
||||||
|
isbest8=istart
|
||||||
|
smax8=sync8
|
||||||
|
endif
|
||||||
|
if(sync1.gt.smax1) then
|
||||||
|
fc21=fc
|
||||||
|
isbest1=istart
|
||||||
|
smax1=sync1
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
! write(*,1022) ifile,icand,isync,fc1, &
|
||||||
|
! fc21,isbest1,smax1,fc28,isbest8,smax8
|
||||||
|
!1022 format(i5,1x,i4,1x,i4,1x,f7.2,1x,2(1x,f7.2,1x,i5,1x,e9.3))
|
||||||
|
enddo
|
||||||
|
|
||||||
|
if(smax8/smax1 .lt. 0.65 ) then
|
||||||
|
fc2=fc21
|
||||||
|
isbest=isbest1
|
||||||
|
ntmax=4
|
||||||
|
if(hmod .gt. 1.0) ntmax=1
|
||||||
|
ntmin=1
|
||||||
|
njitter=2
|
||||||
|
else
|
||||||
|
fc2=fc28
|
||||||
|
isbest=isbest8
|
||||||
|
ntmax=4
|
||||||
|
if(hmod .gt. 1.0) ntmax=1
|
||||||
|
ntmin=1
|
||||||
|
njitter=2
|
||||||
|
endif
|
||||||
|
fc_synced = fc0 + fc2
|
||||||
|
dt_synced = (isbest-fs2)*dt2 !nominal dt is 1 second so frame starts at sample fs2
|
||||||
|
|
||||||
|
call fst280_downsample(c_bigfft,nfft1,ndown,fc_synced,c2)
|
||||||
|
|
||||||
|
if(abs((isbest-fs2)/nss) .lt. 0.2 .and. abs(fc_synced-1500.0).lt.0.4) then
|
||||||
|
ngoodsync=ngoodsync+1
|
||||||
|
endif
|
||||||
|
|
||||||
|
do ijitter=0,2
|
||||||
|
if(ijitter.eq.0) ioffset=0
|
||||||
|
if(ijitter.eq.1) ioffset=2
|
||||||
|
if(ijitter.eq.2) ioffset=-2
|
||||||
|
is0=isbest+ioffset
|
||||||
|
if(is0.lt.0) cycle
|
||||||
|
cframe=c2(is0:is0+164*nss-1)
|
||||||
|
s2=sum(cframe*conjg(cframe))
|
||||||
|
cframe=cframe/sqrt(s2)
|
||||||
|
call get_fst280_bitmetrics(cframe,nss,hmod,bitmetrics,badsync)
|
||||||
|
|
||||||
|
hbits=0
|
||||||
|
where(bitmetrics(:,1).ge.0) hbits=1
|
||||||
|
ns1=count(hbits( 1: 8).eq.(/0,0,0,1,1,0,1,1/))
|
||||||
|
ns2=count(hbits( 9: 16).eq.(/0,1,0,0,1,1,1,0/))
|
||||||
|
ns3=count(hbits(157:164).eq.(/0,0,0,1,1,0,1,1/))
|
||||||
|
ns4=count(hbits(165:172).eq.(/0,1,0,0,1,1,1,0/))
|
||||||
|
ns5=count(hbits(313:320).eq.(/0,0,0,1,1,0,1,1/))
|
||||||
|
ns6=count(hbits(321:328).eq.(/0,1,0,0,1,1,1,0/))
|
||||||
|
nsync_qual=ns1+ns2+ns3+ns4+ns5+ns6
|
||||||
|
! if(nsync_qual.lt. 20) cycle
|
||||||
|
|
||||||
|
scalefac=2.83
|
||||||
|
llra( 1:140)=bitmetrics( 17:156, 1)
|
||||||
|
llra(141:280)=bitmetrics(173:312, 1)
|
||||||
|
llra=scalefac*llra
|
||||||
|
llrb( 1:140)=bitmetrics( 17:156, 2)
|
||||||
|
llrb(141:280)=bitmetrics(173:312, 2)
|
||||||
|
llrb=scalefac*llrb
|
||||||
|
llrc( 1:140)=bitmetrics( 17:156, 3)
|
||||||
|
llrc(141:280)=bitmetrics(173:312, 3)
|
||||||
|
llrc=scalefac*llrc
|
||||||
|
llrd( 1:140)=bitmetrics( 17:156, 4)
|
||||||
|
llrd(141:280)=bitmetrics(173:312, 4)
|
||||||
|
llrd=scalefac*llrd
|
||||||
|
apmask=0
|
||||||
|
|
||||||
|
do itry=ntmax,ntmin,-1
|
||||||
|
if(itry.eq.1) llr=llra
|
||||||
|
if(itry.eq.2) llr=llrb
|
||||||
|
if(itry.eq.3) llr=llrc
|
||||||
|
if(itry.eq.4) llr=llrd
|
||||||
|
dmin=0.0
|
||||||
|
nharderrors=-1
|
||||||
|
unpk77_success=.false.
|
||||||
|
if(iwspr.eq.0) then
|
||||||
|
maxosd=2
|
||||||
|
call decode280_101(llr,Keff,maxosd,ndeep,apmask,message101,cw,ntype,nharderrors,dmin)
|
||||||
|
else
|
||||||
|
maxosd=2
|
||||||
|
call decode280_74(llr,Keff,maxosd,ndeep,apmask,message74,cw,ntype,nharderrors,dmin)
|
||||||
|
endif
|
||||||
|
if(nharderrors .ge.0) then
|
||||||
|
if(iwspr.eq.0) then
|
||||||
|
write(c77,'(77i1)') message101(1:77)
|
||||||
|
call unpack77(c77,0,msg,unpk77_success)
|
||||||
|
else
|
||||||
|
write(c77,'(50i1)') message74(1:50)
|
||||||
|
c77(51:77)='000000000000000000000110000'
|
||||||
|
call unpack77(c77,0,msg,unpk77_success)
|
||||||
|
endif
|
||||||
|
if(nharderrors .ge.0 .and. unpk77_success) then
|
||||||
|
ngood=ngood+1
|
||||||
|
write(*,1100) nfile,icand,xsnr,dt_synced,fc_synced, &
|
||||||
|
itry,ntype,nharderrors,dmin,ijitter,nsync_qual,msg(1:22)
|
||||||
|
1100 format(i5,i5,f6.1,f6.2,f7.1,i4,i4,i4,f7.2,i6,i6,2x,a22)
|
||||||
|
goto 2002
|
||||||
|
else
|
||||||
|
cycle
|
||||||
|
endif
|
||||||
|
endif
|
||||||
|
enddo ! metrics
|
||||||
|
enddo ! istart jitter
|
||||||
|
2002 continue
|
||||||
|
enddo !candidate list
|
||||||
|
enddo !files
|
||||||
|
nfiles=nargs-iarg+1
|
||||||
|
write(*,*) 'nfiles: ',nfiles,' ngood: ',ngood,' ngoodsync: ',ngoodsync
|
||||||
|
write(*,1120)
|
||||||
|
1120 format("<DecodeFinished>")
|
||||||
|
|
||||||
|
999 end program fst280d
|
||||||
|
|
||||||
|
subroutine sync_fst280(cd0,i0,f0,hmod,ncoh,np,nss,fs,sync)
|
||||||
|
|
||||||
|
! Compute sync power for a complex, downsampled FST280 signal.
|
||||||
|
|
||||||
|
include 'ft4s280_params.f90'
|
||||||
|
complex cd0(0:np-1)
|
||||||
|
complex, allocatable, save :: csync(:)
|
||||||
|
complex, allocatable, save :: csynct(:)
|
||||||
|
complex ctwk(8*nss)
|
||||||
|
complex z1,z2,z3
|
||||||
|
logical first
|
||||||
|
integer isyncword(0:7)
|
||||||
|
real f0save
|
||||||
|
data isyncword/0,1,3,2,1,0,2,3/
|
||||||
|
data first/.true./
|
||||||
|
data f0save/0.0/
|
||||||
|
save first,twopi,dt,fac,f0save
|
||||||
|
|
||||||
|
p(z1)=(real(z1*fac)**2 + aimag(z1*fac)**2)**0.5 !Statement function for power
|
||||||
|
|
||||||
|
if( first ) then
|
||||||
|
allocate( csync(8*nss) )
|
||||||
|
allocate( csynct(8*nss) )
|
||||||
|
twopi=8.0*atan(1.0)
|
||||||
|
dt=1/fs
|
||||||
|
k=1
|
||||||
|
phi=0.0
|
||||||
|
do i=0,7
|
||||||
|
dphi=twopi*hmod*(isyncword(i)-1.5)/real(nss)
|
||||||
|
do j=1,nss
|
||||||
|
csync(k)=cmplx(cos(phi),sin(phi))
|
||||||
|
phi=mod(phi+dphi,twopi)
|
||||||
|
k=k+1
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
first=.false.
|
||||||
|
fac=1.0/(8.0*nss)
|
||||||
|
endif
|
||||||
|
|
||||||
|
if(f0.ne.f0save) then
|
||||||
|
dphi=twopi*f0*dt
|
||||||
|
phi=0.0
|
||||||
|
do i=1,8*nss
|
||||||
|
ctwk(i)=cmplx(cos(phi),sin(phi))
|
||||||
|
phi=mod(phi+dphi,twopi)
|
||||||
|
enddo
|
||||||
|
csynct=ctwk*csync
|
||||||
|
f0save=f0
|
||||||
|
endif
|
||||||
|
|
||||||
|
i1=i0 !Costas arrays
|
||||||
|
i2=i0+78*nss
|
||||||
|
i3=i0+156*nss
|
||||||
|
|
||||||
|
s1=0.0
|
||||||
|
s2=0.0
|
||||||
|
s3=0.0
|
||||||
|
nsec=8/ncoh
|
||||||
|
do i=1,nsec
|
||||||
|
is=(i-1)*ncoh*nss
|
||||||
|
z1=sum(cd0(i1+is:i1+is+ncoh*nss-1)*conjg(csynct(is+1:is+ncoh*nss)))
|
||||||
|
z2=sum(cd0(i2+is:i2+is+ncoh*nss-1)*conjg(csynct(is+1:is+ncoh*nss)))
|
||||||
|
z3=sum(cd0(i3+is:i3+is+ncoh*nss-1)*conjg(csynct(is+1:is+ncoh*nss)))
|
||||||
|
s1=s1+abs(z1)/(8*nss)
|
||||||
|
s2=s2+abs(z2)/(8*nss)
|
||||||
|
s3=s3+abs(z3)/(8*nss)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
sync = s1+s2+s3
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine sync_fst280
|
||||||
|
|
||||||
|
subroutine fst280_downsample(c_bigfft,nfft1,ndown,f0,c1)
|
||||||
|
|
||||||
|
! Output: Complex data in c(), sampled at 12000/ndown Hz
|
||||||
|
|
||||||
|
complex c_bigfft(0:nfft1/2)
|
||||||
|
complex c1(0:nfft1/ndown-1)
|
||||||
|
|
||||||
|
df=12000.0/nfft1
|
||||||
|
i0=nint(f0/df)
|
||||||
|
c1(0)=c_bigfft(i0)
|
||||||
|
nfft2=nfft1/ndown
|
||||||
|
do i=1,nfft2/2
|
||||||
|
if(i0+i.le.nfft1/2) c1(i)=c_bigfft(i0+i)
|
||||||
|
if(i0-i.ge.0) c1(nfft2-i)=c_bigfft(i0-i)
|
||||||
|
enddo
|
||||||
|
c1=c1/nfft2
|
||||||
|
call four2a(c1,nfft2,1,1,1) !c2c FFT back to time domain
|
||||||
|
return
|
||||||
|
|
||||||
|
end subroutine fst280_downsample
|
||||||
|
|
||||||
|
subroutine get_candidates_fst280(c_bigfft,nfft1,nsps,hmod,fs,fa,fb,ncand,candidates)
|
||||||
|
|
||||||
|
complex c_bigfft(0:nfft1/2)
|
||||||
|
real candidates(100,3)
|
||||||
|
real s(18000)
|
||||||
|
real s2(18000)
|
||||||
|
data nfft1z/-1/
|
||||||
|
save nfft1z
|
||||||
|
|
||||||
|
nh1=nfft1/2
|
||||||
|
df1=fs/nfft1
|
||||||
|
baud=fs/nsps
|
||||||
|
df2=baud/2.0
|
||||||
|
nd=df1/df2
|
||||||
|
ndh=nd/2
|
||||||
|
ia=fa/df2
|
||||||
|
ib=fb/df2
|
||||||
|
s=0.
|
||||||
|
do i=ia,ib
|
||||||
|
j0=nint(i*df2/df1)
|
||||||
|
do j=j0-ndh,j0+ndh
|
||||||
|
s(i)=s(i) + real(c_bigfft(j))**2 + aimag(c_bigfft(j))**2
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
call pctile(s(ia:ib),ib-ia+1,30,base)
|
||||||
|
s=s/base
|
||||||
|
nh=hmod
|
||||||
|
do i=ia,ib
|
||||||
|
s2(i)=s(i-nh*3) + s(i-nh) +s(i+nh) +s(i+nh*3)
|
||||||
|
s2(i)=db(s2(i)) - 48.5
|
||||||
|
enddo
|
||||||
|
|
||||||
|
if(nh.eq.1) thresh=-29.5
|
||||||
|
if(nh.eq.2) thresh=-27.0
|
||||||
|
if(nh.eq.4) thresh=-25.0
|
||||||
|
|
||||||
|
ncand=0
|
||||||
|
do i=ia,ib
|
||||||
|
if((s2(i).gt.s2(i-1)).and. &
|
||||||
|
(s2(i).gt.s2(i+1)).and. &
|
||||||
|
(s2(i).gt.thresh).and.ncand.lt.100) then
|
||||||
|
ncand=ncand+1
|
||||||
|
candidates(ncand,1)=df2*i
|
||||||
|
candidates(ncand,2)=s2(i)
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine get_candidates_fst280
|
147
lib/fst280/fst280sim.f90
Normal file
147
lib/fst280/fst280sim.f90
Normal file
@ -0,0 +1,147 @@
|
|||||||
|
program fst280sim
|
||||||
|
|
||||||
|
! Generate simulated signals for experimental slow FT4 mode
|
||||||
|
|
||||||
|
use wavhdr
|
||||||
|
use packjt77
|
||||||
|
include 'ft4s280_params.f90' !Set various constants
|
||||||
|
type(hdr) h !Header for .wav file
|
||||||
|
character arg*12,fname*17
|
||||||
|
character msg37*37,msgsent37*37,c77*77
|
||||||
|
character tr_designator*1
|
||||||
|
complex, allocatable :: c0(:)
|
||||||
|
complex, allocatable :: c(:)
|
||||||
|
real, allocatable :: wave(:)
|
||||||
|
integer itone(NN)
|
||||||
|
integer*1 msgbits(101)
|
||||||
|
integer*2, allocatable :: iwave(:) !Generated full-length waveform
|
||||||
|
|
||||||
|
! Get command-line argument(s)
|
||||||
|
nargs=iargc()
|
||||||
|
if(nargs.ne.9) then
|
||||||
|
print*,'Usage: fst280sim "message" type f0 DT h fdop del nfiles snr'
|
||||||
|
print*,'Examples: fst280sim "K1JT K9AN EN50" C 1500 0.0 1.0 0.1 1.0 10 -15'
|
||||||
|
print*,'A: 15 sec'
|
||||||
|
print*,'B: 30 sec'
|
||||||
|
print*,'C: 1 min'
|
||||||
|
print*,'D: 2 min'
|
||||||
|
print*,'E: 5 min'
|
||||||
|
go to 999
|
||||||
|
endif
|
||||||
|
call getarg(1,msg37) !Message to be transmitted
|
||||||
|
call getarg(2,arg)
|
||||||
|
read(arg,*) tr_designator !TR selector
|
||||||
|
call getarg(3,arg)
|
||||||
|
read(arg,*) f0 !Frequency (only used for single-signal)
|
||||||
|
call getarg(4,arg)
|
||||||
|
read(arg,*) xdt !Time offset from nominal (s)
|
||||||
|
call getarg(5,arg)
|
||||||
|
read(arg,*) hmod !Modulation index, h
|
||||||
|
call getarg(6,arg)
|
||||||
|
read(arg,*) fspread !Watterson frequency spread (Hz)
|
||||||
|
call getarg(7,arg)
|
||||||
|
read(arg,*) delay !Watterson delay (ms)
|
||||||
|
call getarg(8,arg)
|
||||||
|
read(arg,*) nfiles !Number of files
|
||||||
|
call getarg(9,arg)
|
||||||
|
read(arg,*) snrdb !SNR_2500
|
||||||
|
|
||||||
|
nfiles=abs(nfiles)
|
||||||
|
twopi=8.0*atan(1.0)
|
||||||
|
fs=12000.0 !Sample rate (Hz)
|
||||||
|
dt=1.0/fs !Sample interval (s)
|
||||||
|
baud=1.0/tt !Keying rate (baud)
|
||||||
|
select case (tr_designator)
|
||||||
|
case('A')
|
||||||
|
nsps=800
|
||||||
|
nmax=15*12000
|
||||||
|
case('B')
|
||||||
|
nsps=1680
|
||||||
|
nmax=30*12000
|
||||||
|
case('C')
|
||||||
|
nsps=4000
|
||||||
|
nmax=60*12000
|
||||||
|
case('D')
|
||||||
|
nsps=8400
|
||||||
|
nmax=120*12000
|
||||||
|
case('E')
|
||||||
|
nsps=21504
|
||||||
|
nmax=300*12000
|
||||||
|
end select
|
||||||
|
nz=nsps*NN
|
||||||
|
nz2=nsps*NN2
|
||||||
|
txt=nz2*dt !Transmission length (s)
|
||||||
|
tt=nsps*dt !Duration of symbols (s)
|
||||||
|
allocate( c0(0:nmax-1) )
|
||||||
|
allocate( c(0:nmax-1) )
|
||||||
|
allocate( wave(nmax) )
|
||||||
|
allocate( iwave(nmax) )
|
||||||
|
|
||||||
|
bandwidth_ratio=2500.0/(fs/2.0)
|
||||||
|
sig=sqrt(2*bandwidth_ratio) * 10.0**(0.05*snrdb)
|
||||||
|
if(snrdb.gt.90.0) sig=1.0
|
||||||
|
|
||||||
|
i3=-1
|
||||||
|
n3=-1
|
||||||
|
call pack77(msg37,i3,n3,c77)
|
||||||
|
call genfst280(msg37,0,msgsent37,msgbits,itone,iwspr)
|
||||||
|
|
||||||
|
write(*,*)
|
||||||
|
write(*,'(a9,a37)') 'Message: ',msgsent37
|
||||||
|
write(*,1000) f0,xdt,hmod,txt,snrdb
|
||||||
|
1000 format('f0:',f9.3,' DT:',f6.2,' hmod:',f6.3,' TxT:',f6.1,' SNR:',f6.1)
|
||||||
|
write(*,*)
|
||||||
|
if(i3.eq.1) then
|
||||||
|
write(*,*) ' mycall hiscall hisgrid'
|
||||||
|
write(*,'(28i1,1x,i1,1x,28i1,1x,i1,1x,i1,1x,15i1,1x,3i1)') msgbits(1:77)
|
||||||
|
else
|
||||||
|
write(*,'(a14)') 'Message bits: '
|
||||||
|
write(*,'(50i1,1x,24i1)') msgbits
|
||||||
|
endif
|
||||||
|
write(*,*)
|
||||||
|
write(*,'(a17)') 'Channel symbols: '
|
||||||
|
write(*,'(10i1)') itone
|
||||||
|
write(*,*)
|
||||||
|
|
||||||
|
! call sgran()
|
||||||
|
|
||||||
|
fsample=12000.0
|
||||||
|
icmplx=1
|
||||||
|
call gen_fst280wave(itone,NN,nsps,nmax,fsample,hmod,f0,icmplx,c0,wave)
|
||||||
|
k=nint((xdt+1.0)/dt)-nsps
|
||||||
|
c0=cshift(c0,-k)
|
||||||
|
if(k.gt.0) c0(0:k-1)=0.0
|
||||||
|
if(k.lt.0) c0(nmax+k:nmax-1)=0.0
|
||||||
|
|
||||||
|
do ifile=1,nfiles
|
||||||
|
c=c0
|
||||||
|
if(fspread.ne.0.0 .or. delay.ne.0.0) call watterson(c,nmax,NZ,fs,delay,fspread)
|
||||||
|
c=sig*c
|
||||||
|
wave=real(c)
|
||||||
|
if(snrdb.lt.90) then
|
||||||
|
do i=1,nmax !Add gaussian noise at specified SNR
|
||||||
|
xnoise=gran()
|
||||||
|
wave(i)=wave(i) + xnoise
|
||||||
|
enddo
|
||||||
|
endif
|
||||||
|
gain=100.0
|
||||||
|
if(snrdb.lt.90.0) then
|
||||||
|
wave=gain*wave
|
||||||
|
else
|
||||||
|
datpk=maxval(abs(wave))
|
||||||
|
fac=32766.9/datpk
|
||||||
|
wave=fac*wave
|
||||||
|
endif
|
||||||
|
if(any(abs(wave).gt.32767.0)) print*,"Warning - data will be clipped."
|
||||||
|
iwave=nint(wave)
|
||||||
|
h=default_header(12000,nmax)
|
||||||
|
write(fname,1102) ifile
|
||||||
|
1102 format('000000_',i6.6,'.wav')
|
||||||
|
open(10,file=fname,status='unknown',access='stream')
|
||||||
|
write(10) h,iwave !Save to *.wav file
|
||||||
|
close(10)
|
||||||
|
write(*,1110) ifile,xdt,f0,snrdb,fname
|
||||||
|
1110 format(i4,f7.2,f8.2,f7.1,2x,a17)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
999 end program fst280sim
|
8
lib/fst280/ft4s280_params.f90
Normal file
8
lib/fst280/ft4s280_params.f90
Normal file
@ -0,0 +1,8 @@
|
|||||||
|
! FT4S280
|
||||||
|
! LDPC(280,101)/CRC24 code, six 4x4 Costas arrays for sync, ramp-up and ramp-down symbols
|
||||||
|
|
||||||
|
parameter (KK=77) !Information bits (77 + CRC24)
|
||||||
|
parameter (ND=140) !Data symbols
|
||||||
|
parameter (NS=24) !Sync symbols
|
||||||
|
parameter (NN=NS+ND) !Sync and data symbols (164)
|
||||||
|
parameter (NN2=NS+ND+2) !Total channel symbols (166)
|
103
lib/fst280/genfst280.f90
Normal file
103
lib/fst280/genfst280.f90
Normal file
@ -0,0 +1,103 @@
|
|||||||
|
subroutine genfst280(msg0,ichk,msgsent,msgbits,i4tone,iwspr)
|
||||||
|
|
||||||
|
! Input:
|
||||||
|
! - msg0 requested message to be transmitted
|
||||||
|
! - ichk if ichk=1, return only msgsent
|
||||||
|
! - msgsent message as it will be decoded
|
||||||
|
! - i4tone array of audio tone values, {0,1,2,3}
|
||||||
|
! - iwspr 0: (280,101)/crc24, 1: (280,74)/crc24
|
||||||
|
!
|
||||||
|
! Frame structure:
|
||||||
|
! s8 d70 s8 d70 s8
|
||||||
|
|
||||||
|
! Message duration: TxT = 164*8400/12000 = 114.8 s
|
||||||
|
|
||||||
|
use packjt77
|
||||||
|
include 'ft4s280_params.f90'
|
||||||
|
character*37 msg0
|
||||||
|
character*37 message !Message to be generated
|
||||||
|
character*37 msgsent !Message as it will be received
|
||||||
|
character*77 c77
|
||||||
|
character*24 c24
|
||||||
|
integer*4 i4tone(NN),itmp(ND)
|
||||||
|
integer*1 codeword(2*ND)
|
||||||
|
integer*1 msgbits(101),rvec(77)
|
||||||
|
integer isyncword(8)
|
||||||
|
integer ncrc24
|
||||||
|
logical unpk77_success
|
||||||
|
data isyncword/0,1,3,2,1,0,2,3/
|
||||||
|
data rvec/0,1,0,0,1,0,1,0,0,1,0,1,1,1,1,0,1,0,0,0,1,0,0,1,1,0,1,1,0, &
|
||||||
|
1,0,0,1,0,1,1,0,0,0,0,1,0,0,0,1,0,1,0,0,1,1,1,1,0,0,1,0,1, &
|
||||||
|
0,1,0,1,0,1,1,0,1,1,1,1,1,0,0,0,1,0,1/
|
||||||
|
message=msg0
|
||||||
|
|
||||||
|
do i=1, 37
|
||||||
|
if(ichar(message(i:i)).eq.0) then
|
||||||
|
message(i:37)=' '
|
||||||
|
exit
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
do i=1,37 !Strip leading blanks
|
||||||
|
if(message(1:1).ne.' ') exit
|
||||||
|
message=message(i+1:)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
i3=-1
|
||||||
|
n3=-1
|
||||||
|
call pack77(message,i3,n3,c77)
|
||||||
|
call unpack77(c77,0,msgsent,unpk77_success) !Unpack to get msgsent
|
||||||
|
msgbits=0
|
||||||
|
iwspr=0
|
||||||
|
if(i3.eq.0.and.n3.eq.6) then
|
||||||
|
iwspr=1
|
||||||
|
read(c77,'(50i1)') msgbits(1:50)
|
||||||
|
call get_crc24(msgbits,74,ncrc24)
|
||||||
|
write(c24,'(b24.24)') ncrc24
|
||||||
|
read(c24,'(24i1)') msgbits(51:74)
|
||||||
|
else
|
||||||
|
read(c77,'(77i1)') msgbits(1:77)
|
||||||
|
call get_crc24(msgbits,101,ncrc24)
|
||||||
|
write(c24,'(b24.24)') ncrc24
|
||||||
|
read(c24,'(24i1)') msgbits(78:101)
|
||||||
|
endif
|
||||||
|
|
||||||
|
if(ichk.eq.1) go to 999
|
||||||
|
if(unpk77_success) go to 2
|
||||||
|
1 msgbits=0
|
||||||
|
itone=0
|
||||||
|
msgsent='*** bad message *** '
|
||||||
|
go to 999
|
||||||
|
|
||||||
|
entry get_ft4s280_tones_from_bits(msgbits,i4tone,iwspr)
|
||||||
|
|
||||||
|
2 continue
|
||||||
|
|
||||||
|
if(iwspr.eq.0) then
|
||||||
|
call encode280_101(msgbits,codeword)
|
||||||
|
else
|
||||||
|
call encode280_74(msgbits(1:74),codeword)
|
||||||
|
endif
|
||||||
|
|
||||||
|
! Grayscale mapping:
|
||||||
|
! bits tone
|
||||||
|
! 00 0
|
||||||
|
! 01 1
|
||||||
|
! 11 2
|
||||||
|
! 10 3
|
||||||
|
|
||||||
|
do i=1,ND
|
||||||
|
is=codeword(2*i)+2*codeword(2*i-1)
|
||||||
|
if(is.le.1) itmp(i)=is
|
||||||
|
if(is.eq.2) itmp(i)=3
|
||||||
|
if(is.eq.3) itmp(i)=2
|
||||||
|
enddo
|
||||||
|
|
||||||
|
i4tone(1:8)=isyncword
|
||||||
|
i4tone(9:78)=itmp(1:70)
|
||||||
|
i4tone(79:86)=isyncword
|
||||||
|
i4tone(87:156)=itmp(71:140)
|
||||||
|
i4tone(157:164)=isyncword
|
||||||
|
|
||||||
|
999 return
|
||||||
|
|
||||||
|
end subroutine genfst280
|
25
lib/fst280/get_crc24.f90
Normal file
25
lib/fst280/get_crc24.f90
Normal file
@ -0,0 +1,25 @@
|
|||||||
|
subroutine get_crc24(mc,len,ncrc)
|
||||||
|
!
|
||||||
|
! 1. To calculate 24-bit CRC, mc(1:len-24) is the message and mc(len-23:len) are zero.
|
||||||
|
! 2. To check a received CRC, mc(1:len) is the received message plus CRC.
|
||||||
|
! ncrc will be zero if the received message/CRC are consistent.
|
||||||
|
!
|
||||||
|
character c24*24
|
||||||
|
integer*1 mc(len)
|
||||||
|
integer*1 r(25),p(25)
|
||||||
|
integer ncrc
|
||||||
|
! polynomial for 24-bit CRC 0x100065b
|
||||||
|
data p/1,0,0,0,0,0,0,0,0,0,0,0,0,0,1,1,0,0,1,0,1,1,0,1,1/
|
||||||
|
|
||||||
|
! divide by polynomial
|
||||||
|
r=mc(1:25)
|
||||||
|
do i=0,len-25
|
||||||
|
r(25)=mc(i+25)
|
||||||
|
r=mod(r+r(1)*p,2)
|
||||||
|
r=cshift(r,1)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
write(c24,'(24b1)') r(1:24)
|
||||||
|
read(c24,'(b24.24)') ncrc
|
||||||
|
|
||||||
|
end subroutine get_crc24
|
118
lib/fst280/get_fst280_bitmetrics.f90
Normal file
118
lib/fst280/get_fst280_bitmetrics.f90
Normal file
@ -0,0 +1,118 @@
|
|||||||
|
subroutine get_fst280_bitmetrics(cd,nss,hmod,bitmetrics,badsync)
|
||||||
|
|
||||||
|
include 'ft4s280_params.f90'
|
||||||
|
complex cd(0:NN*nss-1)
|
||||||
|
complex cs(0:3,NN)
|
||||||
|
complex csymb(nss)
|
||||||
|
complex, allocatable, save :: c1(:,:) ! ideal waveforms, 20 samples per symbol, 4 tones
|
||||||
|
complex cp(0:3) ! accumulated phase shift over symbol types 0:3
|
||||||
|
complex csum,cterm
|
||||||
|
integer icos8(0:7)
|
||||||
|
integer graymap(0:3)
|
||||||
|
integer ip(1)
|
||||||
|
logical one(0:65535,0:15) ! 65536 8-symbol sequences, 16 bits
|
||||||
|
logical first
|
||||||
|
logical badsync
|
||||||
|
real bitmetrics(2*NN,4)
|
||||||
|
real s2(0:65535)
|
||||||
|
real s4(0:3,NN)
|
||||||
|
data icos8/0,1,3,2,1,0,2,3/
|
||||||
|
data graymap/0,1,3,2/
|
||||||
|
data first/.true./
|
||||||
|
save first,one,cp
|
||||||
|
|
||||||
|
if(first) then
|
||||||
|
allocate(c1(nss,0:3))
|
||||||
|
one=.false.
|
||||||
|
do i=0,65535
|
||||||
|
do j=0,15
|
||||||
|
if(iand(i,2**j).ne.0) one(i,j)=.true.
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
twopi=8.0*atan(1.0)
|
||||||
|
dphi=twopi*hmod/nss
|
||||||
|
do itone=0,3
|
||||||
|
dp=(itone-1.5)*dphi
|
||||||
|
phi=0.0
|
||||||
|
do j=1,nss
|
||||||
|
c1(j,itone)=cmplx(cos(phi),sin(phi))
|
||||||
|
phi=mod(phi+dp,twopi)
|
||||||
|
enddo
|
||||||
|
cp(itone)=cmplx(cos(phi),sin(phi))
|
||||||
|
enddo
|
||||||
|
first=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
do k=1,NN
|
||||||
|
i1=(k-1)*NSS
|
||||||
|
csymb=cd(i1:i1+NSS-1)
|
||||||
|
do itone=0,3
|
||||||
|
cs(itone,k)=sum(csymb*conjg(c1(:,itone)))
|
||||||
|
enddo
|
||||||
|
s4(0:3,k)=abs(cs(0:3,k))
|
||||||
|
enddo
|
||||||
|
|
||||||
|
! Sync quality check
|
||||||
|
is1=0
|
||||||
|
is2=0
|
||||||
|
is3=0
|
||||||
|
badsync=.false.
|
||||||
|
ibmax=0
|
||||||
|
|
||||||
|
do k=1,8
|
||||||
|
ip=maxloc(s4(:,k))
|
||||||
|
if(icos8(k-1).eq.(ip(1)-1)) is1=is1+1
|
||||||
|
ip=maxloc(s4(:,k+78))
|
||||||
|
if(icos8(k-1).eq.(ip(1)-1)) is2=is2+1
|
||||||
|
ip=maxloc(s4(:,k+156))
|
||||||
|
if(icos8(k-1).eq.(ip(1)-1)) is3=is3+1
|
||||||
|
enddo
|
||||||
|
nsync=is1+is2+is3 !Number of correct hard sync symbols, 0-24
|
||||||
|
|
||||||
|
badsync=.false.
|
||||||
|
! if(nsync .lt. 8) then
|
||||||
|
! badsync=.true.
|
||||||
|
! return
|
||||||
|
! endif
|
||||||
|
|
||||||
|
bitmetrics=0.0
|
||||||
|
do nseq=1,4 !Try coherent sequences of 1, 2, and 4 symbols
|
||||||
|
if(nseq.eq.1) nsym=1
|
||||||
|
if(nseq.eq.2) nsym=2
|
||||||
|
if(nseq.eq.3) nsym=4
|
||||||
|
if(nseq.eq.4) nsym=8
|
||||||
|
nt=4**nsym
|
||||||
|
do ks=1,NN-nsym+1,nsym
|
||||||
|
s2=0
|
||||||
|
do i=0,nt-1
|
||||||
|
csum=0
|
||||||
|
cterm=1
|
||||||
|
do j=0,nsym-1
|
||||||
|
ntone=mod(i/4**(nsym-1-j),4)
|
||||||
|
csum=csum+cs(graymap(ntone),ks+j)*cterm
|
||||||
|
cterm=cterm*conjg(cp(graymap(ntone)))
|
||||||
|
enddo
|
||||||
|
s2(i)=abs(csum)
|
||||||
|
enddo
|
||||||
|
ipt=1+(ks-1)*2
|
||||||
|
if(nsym.eq.1) ibmax=1
|
||||||
|
if(nsym.eq.2) ibmax=3
|
||||||
|
if(nsym.eq.4) ibmax=7
|
||||||
|
if(nsym.eq.8) ibmax=15
|
||||||
|
do ib=0,ibmax
|
||||||
|
bm=maxval(s2(0:nt-1),one(0:nt-1,ibmax-ib)) - &
|
||||||
|
maxval(s2(0:nt-1),.not.one(0:nt-1,ibmax-ib))
|
||||||
|
if(ipt+ib.gt.2*NN) cycle
|
||||||
|
bitmetrics(ipt+ib,nseq)=bm
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
bitmetrics(321:328,4)=bitmetrics(321:328,3)
|
||||||
|
|
||||||
|
call normalizebmet(bitmetrics(:,1),2*NN)
|
||||||
|
call normalizebmet(bitmetrics(:,2),2*NN)
|
||||||
|
call normalizebmet(bitmetrics(:,3),2*NN)
|
||||||
|
call normalizebmet(bitmetrics(:,4),2*NN)
|
||||||
|
return
|
||||||
|
|
||||||
|
end subroutine get_fst280_bitmetrics
|
182
lib/fst280/ldpc_280_101_generator.f90
Normal file
182
lib/fst280/ldpc_280_101_generator.f90
Normal file
@ -0,0 +1,182 @@
|
|||||||
|
character*26 g(179)
|
||||||
|
|
||||||
|
data g/ &
|
||||||
|
"c919bcbfe4091279702a761e98", &
|
||||||
|
"51b952dddd36200cf73cc1ed30", &
|
||||||
|
"15871d32e8e888439180cf6fd8", &
|
||||||
|
"581f858f6c89ee5ccb91664358", &
|
||||||
|
"3515e85cedf905eda366a8fc20", &
|
||||||
|
"e9fcaa6aaa9bab21bc91174e80", &
|
||||||
|
"0ac73221d424e8747628b13968", &
|
||||||
|
"4999f7116446f1a7a7a1453a30", &
|
||||||
|
"0e92773bff2a6d4f09caa48898", &
|
||||||
|
"7dfaec97c17679f6c3b6a425f0", &
|
||||||
|
"00707d76a2a7d90297ee39f660", &
|
||||||
|
"8048cc93fc4ad84ccfc021e6e0", &
|
||||||
|
"0c13df64062fed419c9bf43400", &
|
||||||
|
"5523d84459c826b7bc3335d508", &
|
||||||
|
"828ee2552144d041ed44ada8e0", &
|
||||||
|
"3f1b89fbd93f674df4813f0898", &
|
||||||
|
"4e13df64062fed419c9bf43400", &
|
||||||
|
"5d8645307d3d442991d6efafd0", &
|
||||||
|
"e5cd9b98d73aab17ce04c4df10", &
|
||||||
|
"06d26e11e2d02e9cb4f191c2b0", &
|
||||||
|
"5630cebc5b3a09f7d4fe58fab0", &
|
||||||
|
"bbfa9591589229738ecbc19288", &
|
||||||
|
"c98654d1f1f16d507e9bb77cf0", &
|
||||||
|
"c2af2107bb2bdff49d909dc730", &
|
||||||
|
"51da7da0c9b1bd18a15f580068", &
|
||||||
|
"5bdfd83e7ca3097146a5359428", &
|
||||||
|
"34fc4d397d97ca3ceb272f49a0", &
|
||||||
|
"6716a6d027ade94010e9aa90b0", &
|
||||||
|
"62ac7bb089d1a13f6e89f92348", &
|
||||||
|
"737c3ab63210e195e92e8ad478", &
|
||||||
|
"db2da5b8a21d22a7122ad80e60", &
|
||||||
|
"1226525dba4221d4768a495878", &
|
||||||
|
"a99deb4c9b7d316917b1ece958", &
|
||||||
|
"8123fb46556f22a0b57bdc7eb0", &
|
||||||
|
"cc6a80e87a7a9bf8addb17a6a8", &
|
||||||
|
"3d42bb6ca1c8d30e6cee77aa10", &
|
||||||
|
"ad15a0c2f36d4409a458cc83c0", &
|
||||||
|
"766a04039736bd8be23513ae58", &
|
||||||
|
"257a3da77558d7c707170c30c8", &
|
||||||
|
"8e54a55fd9f00eb669ab787678", &
|
||||||
|
"4ef1a73cc9da8670d83bebc588", &
|
||||||
|
"be8bb82558d44fea1ab27376a0", &
|
||||||
|
"ea9db4f88c60edf410cb0128d8", &
|
||||||
|
"a84e19a5261818262ee7247278", &
|
||||||
|
"51f99e4ea17cf84038d4e00bd0", &
|
||||||
|
"610560db4095fc44d2465308a0", &
|
||||||
|
"7688745b59c3d6baa6950c4f50", &
|
||||||
|
"4b8794914d365b6802bd62a9c8", &
|
||||||
|
"f62c211d05ed28802b9d278298", &
|
||||||
|
"b9cd45b2ffa8c0dd688f8d2bc0", &
|
||||||
|
"68555e81f4227a48e76878bc98", &
|
||||||
|
"7ab58f11d41a2d38b80d2a7558", &
|
||||||
|
"aba2d33e69077b6acad393af68", &
|
||||||
|
"81e5f58fa3ab563e73706201a8", &
|
||||||
|
"7586aea816750c41671eaa7db8", &
|
||||||
|
"af37b0a97ba5334a3dd01948e8", &
|
||||||
|
"4fdc03c263a0c42dcc265f7dc8", &
|
||||||
|
"b23f2d7f28748944cdfffd5af0", &
|
||||||
|
"5c1e6f37dfba8feacaafdb0f78", &
|
||||||
|
"3a85b051f4f1c930d921f60828", &
|
||||||
|
"72319352bd8022ce2cae2e7858", &
|
||||||
|
"78b79f633ac6879e3ac3a005a0", &
|
||||||
|
"9f0c470609669953b23328de60", &
|
||||||
|
"86d3745d50142c82a066ab9490", &
|
||||||
|
"743e7bf411490f36a9799e37e8", &
|
||||||
|
"9b8378677870933ef360d7e418", &
|
||||||
|
"5f7adbf515b663a1434b0d47d8", &
|
||||||
|
"13249a96b14c6cdcfae5009eb0", &
|
||||||
|
"da9570e0a52125d0dc4dec4430", &
|
||||||
|
"ada13ce2dbcb57e2f5b31172f0", &
|
||||||
|
"84f5485886d4157e9d37efb4d0", &
|
||||||
|
"23f58c3200bab4ae5dee54edd0", &
|
||||||
|
"d4377aadf8acb19d4369613ac8", &
|
||||||
|
"17cefcf65c87885fb6c4d537a0", &
|
||||||
|
"59d70b8536488298930aaea7f8", &
|
||||||
|
"49e8dbb08c2ecdaa84bb6a5378", &
|
||||||
|
"e1694479ecc1f87e503f959e50", &
|
||||||
|
"dbb3fc94f0f70d4bd4dcf302d8", &
|
||||||
|
"4ccb3a56f80c236424683b1588", &
|
||||||
|
"f4f123c72596a00397d56fcdf8", &
|
||||||
|
"13f9cf266a6957b87cd2b576f0", &
|
||||||
|
"0904d341bc0878460cd8361ac0", &
|
||||||
|
"69fd534caf2cccf9c90659a038", &
|
||||||
|
"757d3d95089a5bc20a7b77c618", &
|
||||||
|
"30df1d7b8124415c73190b08d8", &
|
||||||
|
"d39319584987dce0c44176d5d8", &
|
||||||
|
"1a81df299eb7434a5b6b9322a0", &
|
||||||
|
"fe4acfab1c22c7bea222f1a6b0", &
|
||||||
|
"2f2fde37fa8f87a318f7bcda10", &
|
||||||
|
"fae712210c23665aa7a3f10620", &
|
||||||
|
"977b8407c7fd22d7715077ee78", &
|
||||||
|
"2ab2b355b3477df0b738c49d48", &
|
||||||
|
"93a2468cfd11a522b310069d88", &
|
||||||
|
"0e5ae6e789ded3c0d436359318", &
|
||||||
|
"9ece0b13a3c06d560a15d3c448", &
|
||||||
|
"838e8bbf5e671503ea72ba3118", &
|
||||||
|
"7c827de9a87d740763c69c6778", &
|
||||||
|
"1fe395e4e2e6d1373602243488", &
|
||||||
|
"f2c4efee3d0ce2e22749be9e20", &
|
||||||
|
"46405cca0e40f36ab83de4a998", &
|
||||||
|
"8b6e931355a79630ef2dbdbdb8", &
|
||||||
|
"10df1d3b8124415c72190b08d8", &
|
||||||
|
"cdff258b07a4f7cfe5c2210ba8", &
|
||||||
|
"1515e85cedf904eda366a8fc20", &
|
||||||
|
"a38276f2d077abc1da5e177868", &
|
||||||
|
"67a7b5ab66f21f391d306c3330", &
|
||||||
|
"29492cc630f9bad1fdedf0c990", &
|
||||||
|
"490a6dd38170eab178f7cebf78", &
|
||||||
|
"ca9db4e88c60edf410cf0128d8", &
|
||||||
|
"e3f1c23fa8531fb1e4c7768d88", &
|
||||||
|
"39d7d8fbbb689b2a9bedfd4dd0", &
|
||||||
|
"d1b952dd5d36200cf734c1ed30", &
|
||||||
|
"0820a5ccb970d1ab109d84d700", &
|
||||||
|
"58bc3c509fcd7874e9b1533ba8", &
|
||||||
|
"08ed7724ac66b7974499b12f40", &
|
||||||
|
"4738529b2fd04afd89184b64b8", &
|
||||||
|
"7155b496e3b9f687135b4c55b8", &
|
||||||
|
"b5d1d3cf38b1765dd730d8b960", &
|
||||||
|
"296de2c373773a869b9cf804c8", &
|
||||||
|
"1cdf18b99bcc47ae72bf59df68", &
|
||||||
|
"ad0888db89dd794be0b2660e98", &
|
||||||
|
"1f2a8db9db19cd4d69a735d930", &
|
||||||
|
"44b720007480382206fdbfbb18", &
|
||||||
|
"c63817aad3801fb993ea9032c0", &
|
||||||
|
"d44707db5a0b489fd48748cca8", &
|
||||||
|
"49f98a67c6e128a5300f7ccc50", &
|
||||||
|
"04849fa9da91d4514355406388", &
|
||||||
|
"dfad3a11788cf6f6517f987de8", &
|
||||||
|
"47078a19e38a0763cabd7c8d70", &
|
||||||
|
"aafa7f864f0da5bc78f8e57ba8", &
|
||||||
|
"8acb5a34e18e111023b3e7b1f8", &
|
||||||
|
"5acc41263d6aa1767e5e6acdc8", &
|
||||||
|
"27623a9f6c1174e35394191820", &
|
||||||
|
"1f2bde9c006b3b687964b1c5e0", &
|
||||||
|
"b01c6e357bce202244b4a88d08", &
|
||||||
|
"61c85d74d7e97576507c9b0e88", &
|
||||||
|
"bcad5a44d75ae40bc43559d268", &
|
||||||
|
"10584eaf319552194418563de0", &
|
||||||
|
"b29b011d717d10a22de0983980", &
|
||||||
|
"2f9b42d7d2299449491c612b20", &
|
||||||
|
"389ba33f5fec3bfb3a0ef86b50", &
|
||||||
|
"3df89f78c19fb27ae7ff19d360", &
|
||||||
|
"65ff6ba4e107aa919a6afb4ff0", &
|
||||||
|
"39b607c3f09679a62e134cd390", &
|
||||||
|
"94ad06f7b7414727d92f998930", &
|
||||||
|
"169200459898ae0bc7f06714a0", &
|
||||||
|
"c7a5a945adebb554cb4d86a830", &
|
||||||
|
"f37c3ab63230e195e92e8ad478", &
|
||||||
|
"559a51262e91aa9ba0fa96af48", &
|
||||||
|
"fb2998ca916a557463d00fb160", &
|
||||||
|
"aa32462ada57a76ae132fc8de8", &
|
||||||
|
"e6df6b19f58bfee0b96b731b90", &
|
||||||
|
"e984335d40a54fe914a6249110", &
|
||||||
|
"ea73d8f3f14bd9fe2374e39120", &
|
||||||
|
"3adab8e51c36f53584e3669c88", &
|
||||||
|
"74ef69f64dc4fef86c3b1fe640", &
|
||||||
|
"d01c6bc112d7ae3e4ba4820a78", &
|
||||||
|
"62923979fd3c3d1153bcaaf338", &
|
||||||
|
"038f72995b5072df8fe5f4dfa0", &
|
||||||
|
"9f07e7cea2f1476fb035978790", &
|
||||||
|
"2a5aad6a75d5c86cab38fd0070", &
|
||||||
|
"a254a09cc3180854688d2aa9c8", &
|
||||||
|
"0495639712a04820f7038ae7c0", &
|
||||||
|
"d99fc716ca825ad45cca8f4518", &
|
||||||
|
"01b8d558073c0377ce67344a50", &
|
||||||
|
"2fbd0f86a17c3f93713fbd09a0", &
|
||||||
|
"c29dc84bec7b4cd00dd1c17380", &
|
||||||
|
"5e6238b823f530ae017a03f0e0", &
|
||||||
|
"51203d329c68b061977d78d4c0", &
|
||||||
|
"1186729e08cf1dfbec30237968", &
|
||||||
|
"40363018b431224a1f559d2908", &
|
||||||
|
"e334e78442b614a0c9a377e1b8", &
|
||||||
|
"ff2eda86339f589f96382f52e0", &
|
||||||
|
"58a30e07fc7a37a4f858623778", &
|
||||||
|
"f5067fe407a4c3b94ce7b63e48", &
|
||||||
|
"1d09ced788a3642bc0ec640ec8", &
|
||||||
|
"17734ca67d53cd9d8595970668", &
|
||||||
|
"47953c2105bd94bff079672740", &
|
||||||
|
"3444682d1dc0ab486036c1b0d0"/
|
476
lib/fst280/ldpc_280_101_parity.f90
Normal file
476
lib/fst280/ldpc_280_101_parity.f90
Normal file
@ -0,0 +1,476 @@
|
|||||||
|
data Mn/ &
|
||||||
|
150, 151, 161, &
|
||||||
|
6, 164, 172, &
|
||||||
|
92, 128, 158, &
|
||||||
|
2, 63, 135, &
|
||||||
|
3, 14, 22, &
|
||||||
|
4, 18, 29, &
|
||||||
|
5, 17, 164, &
|
||||||
|
7, 99, 179, &
|
||||||
|
8, 88, 115, &
|
||||||
|
9, 62, 110, &
|
||||||
|
10, 107, 154, &
|
||||||
|
11, 50, 140, &
|
||||||
|
12, 28, 33, &
|
||||||
|
13, 31, 170, &
|
||||||
|
15, 69, 175, &
|
||||||
|
16, 77, 178, &
|
||||||
|
19, 70, 91, &
|
||||||
|
20, 95, 177, &
|
||||||
|
21, 96, 106, &
|
||||||
|
23, 129, 168, &
|
||||||
|
24, 49, 169, &
|
||||||
|
25, 65, 102, &
|
||||||
|
26, 82, 171, &
|
||||||
|
27, 45, 137, &
|
||||||
|
30, 89, 119, &
|
||||||
|
32, 148, 158, &
|
||||||
|
34, 94, 152, &
|
||||||
|
35, 44, 92, &
|
||||||
|
36, 39, 138, &
|
||||||
|
37, 55, 58, &
|
||||||
|
38, 121, 165, &
|
||||||
|
40, 81, 162, &
|
||||||
|
41, 139, 150, &
|
||||||
|
42, 43, 83, &
|
||||||
|
46, 80, 114, &
|
||||||
|
47, 52, 54, &
|
||||||
|
48, 166, 173, &
|
||||||
|
38, 53, 87, &
|
||||||
|
56, 64, 126, &
|
||||||
|
57, 67, 127, &
|
||||||
|
59, 156, 159, &
|
||||||
|
60, 97, 133, &
|
||||||
|
61, 118, 161, &
|
||||||
|
66, 100, 123, &
|
||||||
|
68, 124, 131, &
|
||||||
|
71, 101, 155, &
|
||||||
|
72, 74, 144, &
|
||||||
|
73, 112, 141, &
|
||||||
|
75, 136, 149, &
|
||||||
|
59, 78, 117, &
|
||||||
|
79, 130, 163, &
|
||||||
|
84, 93, 113, &
|
||||||
|
86, 108, 163, &
|
||||||
|
103, 146, 157, &
|
||||||
|
70, 104, 145, &
|
||||||
|
105, 128, 142, &
|
||||||
|
74, 109, 122, &
|
||||||
|
54, 111, 153, &
|
||||||
|
116, 154, 176, &
|
||||||
|
120, 132, 167, &
|
||||||
|
21, 125, 147, &
|
||||||
|
134, 143, 166, &
|
||||||
|
7, 81, 160, &
|
||||||
|
32, 99, 174, &
|
||||||
|
1, 93, 104, &
|
||||||
|
2, 69, 98, &
|
||||||
|
3, 33, 152, &
|
||||||
|
4, 46, 159, &
|
||||||
|
5, 126, 178, &
|
||||||
|
6, 127, 147, &
|
||||||
|
8, 101, 110, &
|
||||||
|
9, 73, 158, &
|
||||||
|
10, 120, 123, &
|
||||||
|
11, 122, 125, &
|
||||||
|
12, 58, 170, &
|
||||||
|
13, 88, 105, &
|
||||||
|
14, 133, 150, &
|
||||||
|
15, 92, 100, &
|
||||||
|
16, 90, 108, &
|
||||||
|
17, 44, 106, &
|
||||||
|
18, 35, 175, &
|
||||||
|
19, 94, 179, &
|
||||||
|
20, 97, 153, &
|
||||||
|
22, 109, 130, &
|
||||||
|
23, 63, 140, &
|
||||||
|
24, 37, 146, &
|
||||||
|
25, 141, 168, &
|
||||||
|
26, 95, 115, &
|
||||||
|
27, 107, 149, &
|
||||||
|
28, 91, 168, &
|
||||||
|
29, 134, 144, &
|
||||||
|
30, 31, 169, &
|
||||||
|
34, 40, 96, &
|
||||||
|
36, 156, 172, &
|
||||||
|
39, 61, 135, &
|
||||||
|
41, 42, 121, &
|
||||||
|
43, 57, 117, &
|
||||||
|
45, 62, 72, &
|
||||||
|
47, 137, 167, &
|
||||||
|
48, 83, 116, &
|
||||||
|
49, 65, 173, &
|
||||||
|
1, 50, 141, &
|
||||||
|
2, 8, 150, &
|
||||||
|
3, 62, 140, &
|
||||||
|
4, 104, 124, &
|
||||||
|
5, 128, 139, &
|
||||||
|
6, 64, 159, &
|
||||||
|
7, 103, 176, &
|
||||||
|
2, 11, 104, &
|
||||||
|
9, 71, 85, &
|
||||||
|
10, 80, 131, &
|
||||||
|
11, 17, 130, &
|
||||||
|
12, 148, 156, &
|
||||||
|
13, 39, 164, &
|
||||||
|
14, 15, 167, &
|
||||||
|
14, 32, 89, &
|
||||||
|
16, 114, 135, &
|
||||||
|
8, 164, 169, &
|
||||||
|
18, 107, 129, &
|
||||||
|
19, 53, 102, &
|
||||||
|
20, 134, 170, &
|
||||||
|
21, 43, 145, &
|
||||||
|
22, 24, 76, &
|
||||||
|
23, 44, 146, &
|
||||||
|
19, 22, 101, &
|
||||||
|
25, 41, 48, &
|
||||||
|
26, 46, 58, &
|
||||||
|
27, 82, 87, &
|
||||||
|
28, 78, 179, &
|
||||||
|
29, 73, 81, &
|
||||||
|
30, 116, 161, &
|
||||||
|
31, 96, 157, &
|
||||||
|
15, 58, 172, &
|
||||||
|
10, 33, 160, &
|
||||||
|
34, 110, 118, &
|
||||||
|
33, 35, 113, &
|
||||||
|
36, 166, 175, &
|
||||||
|
32, 37, 152, &
|
||||||
|
38, 57, 74, &
|
||||||
|
13, 82, 176, &
|
||||||
|
40, 42, 45, &
|
||||||
|
25, 57, 177, &
|
||||||
|
40, 120, 136, &
|
||||||
|
21, 92, 121, &
|
||||||
|
23, 34, 147, &
|
||||||
|
12, 45, 54, &
|
||||||
|
3, 46, 48, &
|
||||||
|
47, 91, 169, &
|
||||||
|
26, 61, 132, &
|
||||||
|
49, 123, 147, &
|
||||||
|
1, 79, 88, &
|
||||||
|
51, 97, 101, &
|
||||||
|
52, 155, 177, &
|
||||||
|
24, 72, 105, &
|
||||||
|
54, 84, 106, &
|
||||||
|
55, 63, 126, &
|
||||||
|
56, 72, 163, &
|
||||||
|
38, 63, 170, &
|
||||||
|
37, 71, 178, &
|
||||||
|
20, 49, 59, &
|
||||||
|
30, 60, 117, &
|
||||||
|
61, 65, 137, &
|
||||||
|
41, 98, 119, &
|
||||||
|
47, 51, 62, &
|
||||||
|
6, 76, 131, &
|
||||||
|
55, 70, 81, &
|
||||||
|
66, 111, 119, &
|
||||||
|
60, 67, 94, &
|
||||||
|
68, 112, 132, &
|
||||||
|
9, 69, 157, &
|
||||||
|
70, 75, 89, &
|
||||||
|
69, 108, 153, &
|
||||||
|
44, 53, 77, &
|
||||||
|
29, 130, 149, &
|
||||||
|
65, 103, 125, &
|
||||||
|
74, 85, 156, &
|
||||||
|
56, 67, 68, &
|
||||||
|
77, 138, 144, &
|
||||||
|
28, 95, 138, &
|
||||||
|
79, 133, 142, &
|
||||||
|
35, 50, 86, &
|
||||||
|
73, 78, 137, &
|
||||||
|
27, 126, 175, &
|
||||||
|
83, 100, 143, &
|
||||||
|
42, 142, 168, &
|
||||||
|
40, 48, 158, &
|
||||||
|
86, 95, 174, &
|
||||||
|
39, 109, 129, &
|
||||||
|
59, 88, 125, &
|
||||||
|
6, 89, 155, &
|
||||||
|
36, 90, 102, &
|
||||||
|
75, 97, 141, &
|
||||||
|
43, 146, 148, &
|
||||||
|
93, 149, 168, &
|
||||||
|
52, 83, 94, &
|
||||||
|
80, 87, 106, &
|
||||||
|
91, 96, 143, &
|
||||||
|
3, 43, 126, &
|
||||||
|
98, 154, 162, &
|
||||||
|
99, 115, 173, &
|
||||||
|
5, 84, 100, &
|
||||||
|
64, 133, 154, &
|
||||||
|
90, 117, 158, &
|
||||||
|
7, 108, 151, &
|
||||||
|
4, 128, 167, &
|
||||||
|
105, 127, 136, &
|
||||||
|
1, 83, 114, &
|
||||||
|
107, 127, 134, &
|
||||||
|
4, 108, 170, &
|
||||||
|
92, 109, 171, &
|
||||||
|
110, 113, 122, &
|
||||||
|
111, 124, 166, &
|
||||||
|
12, 112, 150, &
|
||||||
|
2, 95, 105, &
|
||||||
|
17, 114, 118, &
|
||||||
|
99, 139, 144, &
|
||||||
|
116, 165, 178, &
|
||||||
|
5, 22, 73, &
|
||||||
|
16, 115, 162, &
|
||||||
|
13, 34, 41, &
|
||||||
|
120, 122, 151, &
|
||||||
|
121, 160, 172, &
|
||||||
|
8, 37, 102, &
|
||||||
|
123, 140, 165, &
|
||||||
|
7, 53, 93, &
|
||||||
|
9, 10, 130, &
|
||||||
|
11, 30, 58, &
|
||||||
|
31, 66, 179, &
|
||||||
|
14, 31, 45, &
|
||||||
|
15, 88, 129, &
|
||||||
|
18, 101, 148, &
|
||||||
|
16, 62, 127, &
|
||||||
|
17, 20, 68, &
|
||||||
|
19, 86, 98, &
|
||||||
|
25, 106, 163, &
|
||||||
|
135, 152, 163, &
|
||||||
|
23, 124, 137, &
|
||||||
|
21, 28, 71, &
|
||||||
|
24, 26, 153, &
|
||||||
|
29, 90, 123, &
|
||||||
|
32, 113, 134, &
|
||||||
|
35, 57, 169, &
|
||||||
|
27, 50, 139, &
|
||||||
|
33, 60, 65, &
|
||||||
|
38, 61, 142, &
|
||||||
|
145, 153, 154, &
|
||||||
|
39, 67, 81, &
|
||||||
|
36, 84, 133, &
|
||||||
|
18, 161, 173, &
|
||||||
|
93, 155, 171, &
|
||||||
|
42, 99, 131, &
|
||||||
|
49, 87, 162, &
|
||||||
|
51, 56, 168, &
|
||||||
|
47, 125, 144, &
|
||||||
|
44, 143, 159, &
|
||||||
|
46, 75, 138, &
|
||||||
|
52, 78, 107, &
|
||||||
|
54, 109, 174, &
|
||||||
|
64, 110, 179, &
|
||||||
|
159, 165, 174, &
|
||||||
|
66, 135, 171, &
|
||||||
|
63, 76, 117, &
|
||||||
|
59, 111, 120, &
|
||||||
|
72, 160, 166, &
|
||||||
|
70, 118, 156, &
|
||||||
|
55, 157, 173, &
|
||||||
|
74, 100, 176, &
|
||||||
|
77, 112, 145, &
|
||||||
|
69, 141, 147, &
|
||||||
|
94, 140, 151, &
|
||||||
|
51, 82, 104, &
|
||||||
|
85, 98, 167, &
|
||||||
|
80, 119, 146, &
|
||||||
|
97, 122, 172, &
|
||||||
|
90, 96, 132, &
|
||||||
|
79, 91, 178, &
|
||||||
|
103, 136, 152, &
|
||||||
|
1, 76, 85, &
|
||||||
|
115, 121, 149, &
|
||||||
|
116, 175, 177/
|
||||||
|
|
||||||
|
data Nm/ &
|
||||||
|
65, 102, 151, 207, 278, 0, &
|
||||||
|
4, 66, 103, 109, 214, 0, &
|
||||||
|
5, 67, 104, 147, 198, 0, &
|
||||||
|
6, 68, 105, 205, 209, 0, &
|
||||||
|
7, 69, 106, 201, 218, 0, &
|
||||||
|
2, 70, 107, 165, 190, 0, &
|
||||||
|
8, 63, 108, 204, 225, 0, &
|
||||||
|
9, 71, 103, 118, 223, 0, &
|
||||||
|
10, 72, 110, 170, 226, 0, &
|
||||||
|
11, 73, 111, 134, 226, 0, &
|
||||||
|
12, 74, 109, 112, 227, 0, &
|
||||||
|
13, 75, 113, 146, 213, 0, &
|
||||||
|
14, 76, 114, 140, 220, 0, &
|
||||||
|
5, 77, 115, 116, 229, 0, &
|
||||||
|
15, 78, 115, 133, 230, 0, &
|
||||||
|
16, 79, 117, 219, 232, 0, &
|
||||||
|
7, 80, 112, 215, 233, 0, &
|
||||||
|
6, 81, 119, 231, 249, 0, &
|
||||||
|
17, 82, 120, 125, 234, 0, &
|
||||||
|
18, 83, 121, 160, 233, 0, &
|
||||||
|
19, 61, 122, 144, 238, 0, &
|
||||||
|
5, 84, 123, 125, 218, 0, &
|
||||||
|
20, 85, 124, 145, 237, 0, &
|
||||||
|
21, 86, 123, 154, 239, 0, &
|
||||||
|
22, 87, 126, 142, 235, 0, &
|
||||||
|
23, 88, 127, 149, 239, 0, &
|
||||||
|
24, 89, 128, 183, 243, 0, &
|
||||||
|
13, 90, 129, 179, 238, 0, &
|
||||||
|
6, 91, 130, 174, 240, 0, &
|
||||||
|
25, 92, 131, 161, 227, 0, &
|
||||||
|
14, 92, 132, 228, 229, 0, &
|
||||||
|
26, 64, 116, 138, 241, 0, &
|
||||||
|
13, 67, 134, 136, 244, 0, &
|
||||||
|
27, 93, 135, 145, 220, 0, &
|
||||||
|
28, 81, 136, 181, 242, 0, &
|
||||||
|
29, 94, 137, 191, 248, 0, &
|
||||||
|
30, 86, 138, 159, 223, 0, &
|
||||||
|
31, 38, 139, 158, 245, 0, &
|
||||||
|
29, 95, 114, 188, 247, 0, &
|
||||||
|
32, 93, 141, 143, 186, 0, &
|
||||||
|
33, 96, 126, 163, 220, 0, &
|
||||||
|
34, 96, 141, 185, 251, 0, &
|
||||||
|
34, 97, 122, 193, 198, 0, &
|
||||||
|
28, 80, 124, 173, 255, 0, &
|
||||||
|
24, 98, 141, 146, 229, 0, &
|
||||||
|
35, 68, 127, 147, 256, 0, &
|
||||||
|
36, 99, 148, 164, 254, 0, &
|
||||||
|
37, 100, 126, 147, 186, 0, &
|
||||||
|
21, 101, 150, 160, 252, 0, &
|
||||||
|
12, 102, 181, 243, 0, 0, &
|
||||||
|
152, 164, 253, 271, 0, 0, &
|
||||||
|
36, 153, 195, 257, 0, 0, &
|
||||||
|
38, 120, 173, 225, 0, 0, &
|
||||||
|
36, 58, 146, 155, 258, 0, &
|
||||||
|
30, 156, 166, 266, 0, 0, &
|
||||||
|
39, 157, 177, 253, 0, 0, &
|
||||||
|
40, 97, 139, 142, 242, 0, &
|
||||||
|
30, 75, 127, 133, 227, 0, &
|
||||||
|
41, 50, 160, 189, 263, 0, &
|
||||||
|
42, 161, 168, 244, 0, 0, &
|
||||||
|
43, 95, 149, 162, 245, 0, &
|
||||||
|
10, 98, 104, 164, 232, 0, &
|
||||||
|
4, 85, 156, 158, 262, 0, &
|
||||||
|
39, 107, 202, 259, 0, 0, &
|
||||||
|
22, 101, 162, 175, 244, 0, &
|
||||||
|
44, 167, 228, 261, 0, 0, &
|
||||||
|
40, 168, 177, 247, 0, 0, &
|
||||||
|
45, 169, 177, 233, 0, 0, &
|
||||||
|
15, 66, 170, 172, 269, 0, &
|
||||||
|
17, 55, 166, 171, 265, 0, &
|
||||||
|
46, 110, 159, 238, 0, 0, &
|
||||||
|
47, 98, 154, 157, 264, 0, &
|
||||||
|
48, 72, 130, 182, 218, 0, &
|
||||||
|
47, 57, 139, 176, 267, 0, &
|
||||||
|
49, 171, 192, 256, 0, 0, &
|
||||||
|
123, 165, 262, 278, 0, 0, &
|
||||||
|
16, 173, 178, 268, 0, 0, &
|
||||||
|
50, 129, 182, 257, 0, 0, &
|
||||||
|
51, 151, 180, 276, 0, 0, &
|
||||||
|
35, 111, 196, 273, 0, 0, &
|
||||||
|
32, 63, 130, 166, 247, 0, &
|
||||||
|
23, 128, 140, 271, 0, 0, &
|
||||||
|
34, 100, 184, 195, 207, 0, &
|
||||||
|
52, 155, 201, 248, 0, 0, &
|
||||||
|
110, 176, 272, 278, 0, 0, &
|
||||||
|
53, 181, 187, 234, 0, 0, &
|
||||||
|
38, 128, 196, 252, 0, 0, &
|
||||||
|
9, 76, 151, 189, 230, 0, &
|
||||||
|
25, 116, 171, 190, 0, 0, &
|
||||||
|
79, 191, 203, 240, 275, 0, &
|
||||||
|
17, 90, 148, 197, 276, 0, &
|
||||||
|
3, 28, 78, 144, 210, 0, &
|
||||||
|
52, 65, 194, 225, 250, 0, &
|
||||||
|
27, 82, 168, 195, 270, 0, &
|
||||||
|
18, 88, 179, 187, 214, 0, &
|
||||||
|
19, 93, 132, 197, 275, 0, &
|
||||||
|
42, 83, 152, 192, 274, 0, &
|
||||||
|
66, 163, 199, 234, 272, 0, &
|
||||||
|
8, 64, 200, 216, 251, 0, &
|
||||||
|
44, 78, 184, 201, 267, 0, &
|
||||||
|
46, 71, 125, 152, 231, 0, &
|
||||||
|
22, 120, 191, 223, 0, 0, &
|
||||||
|
54, 108, 175, 277, 0, 0, &
|
||||||
|
55, 65, 105, 109, 271, 0, &
|
||||||
|
56, 76, 154, 206, 214, 0, &
|
||||||
|
19, 80, 155, 196, 235, 0, &
|
||||||
|
11, 89, 119, 208, 257, 0, &
|
||||||
|
53, 79, 172, 204, 209, 0, &
|
||||||
|
57, 84, 188, 210, 258, 0, &
|
||||||
|
10, 71, 135, 211, 259, 0, &
|
||||||
|
58, 167, 212, 263, 0, 0, &
|
||||||
|
48, 169, 213, 268, 0, 0, &
|
||||||
|
52, 136, 211, 241, 0, 0, &
|
||||||
|
35, 117, 207, 215, 0, 0, &
|
||||||
|
9, 88, 200, 219, 279, 0, &
|
||||||
|
59, 100, 131, 217, 280, 0, &
|
||||||
|
50, 97, 161, 203, 262, 0, &
|
||||||
|
43, 135, 215, 265, 0, 0, &
|
||||||
|
25, 163, 167, 273, 0, 0, &
|
||||||
|
60, 73, 143, 221, 263, 0, &
|
||||||
|
31, 96, 144, 222, 279, 0, &
|
||||||
|
57, 74, 211, 221, 274, 0, &
|
||||||
|
44, 73, 150, 224, 240, 0, &
|
||||||
|
45, 105, 212, 237, 0, 0, &
|
||||||
|
61, 74, 175, 189, 254, 0, &
|
||||||
|
39, 69, 156, 183, 198, 0, &
|
||||||
|
40, 70, 206, 208, 232, 0, &
|
||||||
|
3, 56, 106, 205, 0, 0, &
|
||||||
|
20, 119, 188, 230, 0, 0, &
|
||||||
|
51, 84, 112, 174, 226, 0, &
|
||||||
|
45, 111, 165, 251, 0, 0, &
|
||||||
|
60, 149, 169, 275, 0, 0, &
|
||||||
|
42, 77, 180, 202, 248, 0, &
|
||||||
|
62, 91, 121, 208, 241, 0, &
|
||||||
|
4, 95, 117, 236, 261, 0, &
|
||||||
|
49, 143, 206, 277, 0, 0, &
|
||||||
|
24, 99, 162, 182, 237, 0, &
|
||||||
|
29, 178, 179, 256, 0, 0, &
|
||||||
|
33, 106, 216, 243, 0, 0, &
|
||||||
|
12, 85, 104, 224, 270, 0, &
|
||||||
|
48, 87, 102, 192, 269, 0, &
|
||||||
|
56, 180, 185, 245, 0, 0, &
|
||||||
|
62, 184, 197, 255, 0, 0, &
|
||||||
|
47, 91, 178, 216, 254, 0, &
|
||||||
|
55, 122, 246, 268, 0, 0, &
|
||||||
|
54, 86, 124, 193, 273, 0, &
|
||||||
|
61, 70, 145, 150, 269, 0, &
|
||||||
|
26, 113, 193, 231, 0, 0, &
|
||||||
|
49, 89, 174, 194, 279, 0, &
|
||||||
|
1, 33, 77, 103, 213, 0, &
|
||||||
|
1, 204, 221, 270, 0, 0, &
|
||||||
|
27, 67, 138, 236, 277, 0, &
|
||||||
|
58, 83, 172, 239, 246, 0, &
|
||||||
|
11, 59, 199, 202, 246, 0, &
|
||||||
|
46, 153, 190, 250, 0, 0, &
|
||||||
|
41, 94, 113, 176, 265, 0, &
|
||||||
|
54, 132, 170, 266, 0, 0, &
|
||||||
|
3, 26, 72, 186, 203, 0, &
|
||||||
|
41, 68, 107, 255, 260, 0, &
|
||||||
|
63, 134, 222, 264, 0, 0, &
|
||||||
|
1, 43, 131, 249, 0, 0, &
|
||||||
|
32, 199, 219, 252, 0, 0, &
|
||||||
|
51, 53, 157, 235, 236, 0, &
|
||||||
|
2, 7, 114, 118, 0, 0, &
|
||||||
|
31, 217, 224, 260, 0, 0, &
|
||||||
|
37, 62, 137, 212, 264, 0, &
|
||||||
|
60, 99, 115, 205, 272, 0, &
|
||||||
|
20, 87, 90, 185, 194, 253, &
|
||||||
|
21, 92, 118, 148, 242, 0, &
|
||||||
|
14, 75, 121, 158, 209, 0, &
|
||||||
|
23, 210, 250, 261, 0, 0, &
|
||||||
|
2, 94, 133, 222, 274, 0, &
|
||||||
|
37, 101, 200, 249, 266, 0, &
|
||||||
|
64, 187, 258, 260, 0, 0, &
|
||||||
|
15, 81, 137, 183, 280, 0, &
|
||||||
|
59, 108, 140, 267, 0, 0, &
|
||||||
|
18, 142, 153, 280, 0, 0, &
|
||||||
|
16, 69, 159, 217, 276, 0, &
|
||||||
|
8, 82, 129, 228, 259, 0/
|
||||||
|
|
||||||
|
data nrw/ &
|
||||||
|
5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5, &
|
||||||
|
5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5, &
|
||||||
|
5,5,5,5,5,5,5,5,5,4,4,4,4,5,4,4,5,5,5,4, &
|
||||||
|
5,5,5,4,5,4,4,4,5,5,4,5,5,5,4,4,4,4,4,4, &
|
||||||
|
5,4,5,4,4,4,4,5,4,5,5,5,5,5,5,5,5,5,5,5, &
|
||||||
|
5,4,4,5,5,5,5,5,5,5,4,4,4,4,5,5,5,4,4,5, &
|
||||||
|
5,5,5,4,5,5,5,4,4,5,4,4,5,5,5,4,5,4,4,5, &
|
||||||
|
5,4,4,5,4,5,5,4,5,5,4,5,5,5,4,5,4,5,5,4, &
|
||||||
|
4,4,5,4,4,5,5,6,5,5,4,5,5,4,5,4,4,5,5/
|
||||||
|
|
||||||
|
ncw=3
|
||||||
|
|
209
lib/fst280/ldpc_280_74_generator.f90
Normal file
209
lib/fst280/ldpc_280_74_generator.f90
Normal file
@ -0,0 +1,209 @@
|
|||||||
|
character*19 g(206)
|
||||||
|
|
||||||
|
data g/ &
|
||||||
|
"f7842fd3230388e2388", &
|
||||||
|
"2ebea0b08a75d2261cc", &
|
||||||
|
"b037d38c9d9b9a5e520", &
|
||||||
|
"936729d89fd5474ecdc", &
|
||||||
|
"539287b4ef7ee4534a8", &
|
||||||
|
"a4d283607d3a5020508", &
|
||||||
|
"f4539f434b8b8585444", &
|
||||||
|
"1c7b56480cc52fa5228", &
|
||||||
|
"a1c788b066ac91de648", &
|
||||||
|
"6592203e5579bbd9248", &
|
||||||
|
"aaa9e1247a75c451654", &
|
||||||
|
"f06cbce3477735fcdac", &
|
||||||
|
"0b3bd1b2eb21c4a58e8", &
|
||||||
|
"9789c1e9afeaefe132c", &
|
||||||
|
"6f3090a344262fe9588", &
|
||||||
|
"523326e51ec096314c0", &
|
||||||
|
"33ad630efa2f0547a1c", &
|
||||||
|
"128e4669c5290997554", &
|
||||||
|
"d21ba68abe8a45c7388", &
|
||||||
|
"14792ff07616833ddcc", &
|
||||||
|
"f336703cec81b57b9d4", &
|
||||||
|
"dcb179c1ede8a193578", &
|
||||||
|
"19a5027744d4d5fc3ec", &
|
||||||
|
"416cb1bc4f9fc83f03c", &
|
||||||
|
"245f12d8a19902ff678", &
|
||||||
|
"3a9653df6b08f65e934", &
|
||||||
|
"94870f042c4015d30d0", &
|
||||||
|
"7db806a2e50336e78bc", &
|
||||||
|
"d799458b3559526d2a8", &
|
||||||
|
"77e7cfd440146912610", &
|
||||||
|
"67c9ca176f188a99b1c", &
|
||||||
|
"dd736cb5cbfaa6f6cb0", &
|
||||||
|
"1210f8c1310dde522e4", &
|
||||||
|
"3bdf62af1d111a616a8", &
|
||||||
|
"556e0b2cb64629c03e0", &
|
||||||
|
"153b771b34fd0e24038", &
|
||||||
|
"677111e1bd26700abec", &
|
||||||
|
"ba6a2362c2249224dc8", &
|
||||||
|
"96d96eda9f7d897b3a4", &
|
||||||
|
"ee632974db8208ed678", &
|
||||||
|
"ba6e8ace7ca7e5dba2c", &
|
||||||
|
"112aa2048b8723c3794", &
|
||||||
|
"04125e68eed114d3a74", &
|
||||||
|
"6ce3283112a3d15df18", &
|
||||||
|
"6717fa02c4245ac3cd4", &
|
||||||
|
"bba51cf56c4ab60d0e8", &
|
||||||
|
"bf02614f56d95557004", &
|
||||||
|
"db8d9537a66dae71170", &
|
||||||
|
"2aa9e1247a75c451614", &
|
||||||
|
"37887845236cdc5a498", &
|
||||||
|
"5a0fd4682a5116e3bd4", &
|
||||||
|
"66a13f0f4838812f4b0", &
|
||||||
|
"0189837a15fb8a3ea28", &
|
||||||
|
"bd833c6eb639530bb4c", &
|
||||||
|
"ad2cb697dcd08717134", &
|
||||||
|
"d28c4e5b0e4f93921e8", &
|
||||||
|
"4a10da97be29877762c", &
|
||||||
|
"11b1d2dbd7e029e0034", &
|
||||||
|
"8cebf77857fd5b4b2d0", &
|
||||||
|
"8cf76e6929f04a6f2d0", &
|
||||||
|
"4dfdef39d983b6ff054", &
|
||||||
|
"e19594dcc430c3f36f8", &
|
||||||
|
"b4e0a5979e86ca9e7d8", &
|
||||||
|
"c6e5822a81c720e1da8", &
|
||||||
|
"d8b1374afa4f4534c2c", &
|
||||||
|
"d50ebca7ce5022d72b8", &
|
||||||
|
"d1af50dba58c8b978d4", &
|
||||||
|
"0114771daca21b8a4e8", &
|
||||||
|
"5a12be303c2bcc6cad0", &
|
||||||
|
"75ba0d26c70194e20dc", &
|
||||||
|
"feeb4567ccdd6d44334", &
|
||||||
|
"de993868f8b317cdb08", &
|
||||||
|
"8c0f2fc7b031a0354ec", &
|
||||||
|
"df2ddab6d334a1316fc", &
|
||||||
|
"d410f54de1453f63024", &
|
||||||
|
"14870f042c4011d30d0", &
|
||||||
|
"bf8bb7654c089ff49f4", &
|
||||||
|
"48fe5211864e84af104", &
|
||||||
|
"a212348c05d3f2f7c8c", &
|
||||||
|
"1cb6e7158001aa32fa0", &
|
||||||
|
"bb2700d89c358ea9f74", &
|
||||||
|
"f5ff926daf5e6003708", &
|
||||||
|
"7eecbcdc28e9800b97c", &
|
||||||
|
"b38c9a3ff4e36761180", &
|
||||||
|
"aff8af260682347a39c", &
|
||||||
|
"24c2e6bf10c093cb8b8", &
|
||||||
|
"7633edd7825917114ec", &
|
||||||
|
"3383b1074eee8343950", &
|
||||||
|
"3d0636cf743b45409bc", &
|
||||||
|
"e6191c1e4753a438054", &
|
||||||
|
"a5ed8c6a5c54aaa2d0c", &
|
||||||
|
"2335c47d4da16e79fd4", &
|
||||||
|
"56f62a484a6243fea04", &
|
||||||
|
"090c7572a6b53ed67d8", &
|
||||||
|
"a12212511d2fe5a7a04", &
|
||||||
|
"55653c6f1cd716dfafc", &
|
||||||
|
"25fb9166056f5276e50", &
|
||||||
|
"b5500cd4a5a4903b794", &
|
||||||
|
"5aaa65c6ee1732ffa20", &
|
||||||
|
"702a7660612fd7307fc", &
|
||||||
|
"bbf00390ef7bb4219f4", &
|
||||||
|
"36a23bd84e7d142dc28", &
|
||||||
|
"00dd156a637e5b6cf34", &
|
||||||
|
"d960448d1d09f7a3d5c", &
|
||||||
|
"7cc7c47ef82e670f740", &
|
||||||
|
"0c72af8643fa31e0df8", &
|
||||||
|
"c60997484551c3304ec", &
|
||||||
|
"5234c7b54ce0fb97cd4", &
|
||||||
|
"e4551cf6ddc5bf7b85c", &
|
||||||
|
"7320bbe8f600cb3f654", &
|
||||||
|
"b25ac980a31e7d449e8", &
|
||||||
|
"da25337deba0f2a1024", &
|
||||||
|
"4b54fafbcdf9f159c70", &
|
||||||
|
"75252e36d57dc65a0c8", &
|
||||||
|
"9f792800ecd943f8784", &
|
||||||
|
"fb7d1b209de7997cd40", &
|
||||||
|
"f47e660b960bf39cda4", &
|
||||||
|
"630017e41ef1e01b3bc", &
|
||||||
|
"047d83c03cd1e69929c", &
|
||||||
|
"0b8be375675a21f6c50", &
|
||||||
|
"aebfa0b08a75d2261cc", &
|
||||||
|
"dcd8bfe5b2b83f3276c", &
|
||||||
|
"862503814b89c46f268", &
|
||||||
|
"caf108899bef63422e0", &
|
||||||
|
"0651e9975e9eb3049bc", &
|
||||||
|
"d2418a98d6be4bb1368", &
|
||||||
|
"0f886c109cbf0643a64", &
|
||||||
|
"ae76a8d1d71335942cc", &
|
||||||
|
"66a0d75d3f90f0d0c04", &
|
||||||
|
"51d30039a555c4ac8cc", &
|
||||||
|
"9d7a4b82e9323439734", &
|
||||||
|
"2475d34a372b289eba4", &
|
||||||
|
"2468b9122171f215a80", &
|
||||||
|
"f1eb642be43a6d15e74", &
|
||||||
|
"001d6a58165ada8f124", &
|
||||||
|
"dd770baa38e1f8c2fd8", &
|
||||||
|
"03e026dcb395529dc0c", &
|
||||||
|
"46dc96eb5146f71a614", &
|
||||||
|
"1402ba94f9d9e1ff3dc", &
|
||||||
|
"dd7970ccb883bf18678", &
|
||||||
|
"29ddaca7cd0bf0151f4", &
|
||||||
|
"865c5ec3ab28496ade4", &
|
||||||
|
"97d388a7557a659e7f8", &
|
||||||
|
"78ba47aec4ff81965dc", &
|
||||||
|
"26a0c75d3f90f0d0c04", &
|
||||||
|
"48bc3be9b33ad3a2960", &
|
||||||
|
"e9c4c425a39b4fa6520", &
|
||||||
|
"2a8cfed864a4c6f5bb8", &
|
||||||
|
"de273ccb39330dd42a0", &
|
||||||
|
"c7e0c4a6641be9a6934", &
|
||||||
|
"f8b8514aebccc0086a4", &
|
||||||
|
"0f2b8fda05f0d07629c", &
|
||||||
|
"8734be755b106490e04", &
|
||||||
|
"789a87c164b552602d4", &
|
||||||
|
"b588408fb1a6c128874", &
|
||||||
|
"9dddcc7da27769ac544", &
|
||||||
|
"288b20a6f933bab6328", &
|
||||||
|
"f38c9a3ff4e26761180", &
|
||||||
|
"dc5613392113fea3498", &
|
||||||
|
"62dcbccf74e9673662c", &
|
||||||
|
"729e135a6b13b1eb084", &
|
||||||
|
"3045e9bb3c808018868", &
|
||||||
|
"0d1e2b1a48642a04dac", &
|
||||||
|
"abb1dced614797b1288", &
|
||||||
|
"d29fba8d71829beb4a0", &
|
||||||
|
"8f4a38515de6db613c4", &
|
||||||
|
"67194fd309de34d2178", &
|
||||||
|
"fc73d1f5ea8fd6bf49c", &
|
||||||
|
"c6289740e2b97b8d29c", &
|
||||||
|
"6100d464faa8f4f3068", &
|
||||||
|
"2cb7e414a3da6ca0988", &
|
||||||
|
"b439b0fdfdf891f28ec", &
|
||||||
|
"b7d3aaa693c7f068120", &
|
||||||
|
"25d691a2bc6288c1c50", &
|
||||||
|
"52f1f88c882d24a5f9c", &
|
||||||
|
"9892d88821ebd874f1c", &
|
||||||
|
"fbda9cdf96a2c4e9b30", &
|
||||||
|
"7716ec58ca1ac237f90", &
|
||||||
|
"6993c923557c6c68b68", &
|
||||||
|
"eb32c8c6a30622d0c28", &
|
||||||
|
"ba7980eafa803e1d3dc", &
|
||||||
|
"a92b5a9ca961bf9a5bc", &
|
||||||
|
"36ecfc5928f2c7be4cc", &
|
||||||
|
"ab854e4b7a9944840d4", &
|
||||||
|
"62db1428386b97101e4", &
|
||||||
|
"734bc6eb48e3024c7a0", &
|
||||||
|
"5b06c92d9089c7e6e38", &
|
||||||
|
"c7d02e44052506c6d14", &
|
||||||
|
"d35f553090ce90d3b04", &
|
||||||
|
"5462cf72405e2525d7c", &
|
||||||
|
"c9b85ab24e5188e5d18", &
|
||||||
|
"d0bb27c6092eb01dc7c", &
|
||||||
|
"37036df9c68bfe4eb24", &
|
||||||
|
"4387156e9b00d277ce0", &
|
||||||
|
"a39bb776102878c96a4", &
|
||||||
|
"d6f1cd9b329e7d0b374", &
|
||||||
|
"d74ba376dbaa9de5270", &
|
||||||
|
"58df754b03e0fa7a714", &
|
||||||
|
"14dfaffe9ab7ba93ce8", &
|
||||||
|
"36652b8b0226f6cc940", &
|
||||||
|
"777234e72dd631499ac", &
|
||||||
|
"581964c38824c5a58f8", &
|
||||||
|
"187cba427974172c6a0", &
|
||||||
|
"a90588951da0399e6f0", &
|
||||||
|
"3ddb7427533342f51cc", &
|
||||||
|
"25d308610cf492a5ac4"/
|
504
lib/fst280/ldpc_280_74_parity.f90
Normal file
504
lib/fst280/ldpc_280_74_parity.f90
Normal file
@ -0,0 +1,504 @@
|
|||||||
|
data Mn/ &
|
||||||
|
95, 150, 172, &
|
||||||
|
154, 178, 184, &
|
||||||
|
1, 90, 164, &
|
||||||
|
2, 143, 199, &
|
||||||
|
3, 33, 70, &
|
||||||
|
4, 23, 86, &
|
||||||
|
5, 127, 174, &
|
||||||
|
6, 18, 110, &
|
||||||
|
7, 59, 99, &
|
||||||
|
8, 94, 124, &
|
||||||
|
9, 168, 206, &
|
||||||
|
10, 165, 175, &
|
||||||
|
11, 64, 166, &
|
||||||
|
12, 103, 156, &
|
||||||
|
13, 46, 80, &
|
||||||
|
14, 35, 172, &
|
||||||
|
15, 20, 189, &
|
||||||
|
16, 162, 188, &
|
||||||
|
17, 74, 200, &
|
||||||
|
19, 52, 178, &
|
||||||
|
21, 87, 182, &
|
||||||
|
22, 30, 144, &
|
||||||
|
24, 37, 126, &
|
||||||
|
25, 107, 171, &
|
||||||
|
26, 114, 187, &
|
||||||
|
27, 36, 53, &
|
||||||
|
28, 91, 169, &
|
||||||
|
29, 100, 109, &
|
||||||
|
31, 71, 192, &
|
||||||
|
32, 106, 190, &
|
||||||
|
34, 160, 204, &
|
||||||
|
38, 93, 136, &
|
||||||
|
39, 77, 196, &
|
||||||
|
40, 43, 177, &
|
||||||
|
41, 56, 66, &
|
||||||
|
42, 115, 151, &
|
||||||
|
44, 155, 180, &
|
||||||
|
45, 105, 128, &
|
||||||
|
47, 54, 203, &
|
||||||
|
48, 117, 120, &
|
||||||
|
49, 62, 183, &
|
||||||
|
50, 185, 202, &
|
||||||
|
51, 83, 147, &
|
||||||
|
55, 75, 170, &
|
||||||
|
57, 79, 205, &
|
||||||
|
58, 67, 159, &
|
||||||
|
60, 81, 201, &
|
||||||
|
61, 89, 184, &
|
||||||
|
63, 119, 198, &
|
||||||
|
65, 104, 152, &
|
||||||
|
68, 149, 191, &
|
||||||
|
69, 134, 167, &
|
||||||
|
72, 102, 129, &
|
||||||
|
73, 95, 108, &
|
||||||
|
76, 82, 146, &
|
||||||
|
78, 112, 173, &
|
||||||
|
84, 141, 161, &
|
||||||
|
85, 138, 157, &
|
||||||
|
92, 132, 145, &
|
||||||
|
96, 131, 181, &
|
||||||
|
97, 110, 121, &
|
||||||
|
98, 133, 153, &
|
||||||
|
74, 101, 195, &
|
||||||
|
111, 118, 183, &
|
||||||
|
113, 130, 163, &
|
||||||
|
116, 176, 193, &
|
||||||
|
125, 188, 194, &
|
||||||
|
135, 142, 148, &
|
||||||
|
28, 137, 140, &
|
||||||
|
33, 68, 150, &
|
||||||
|
46, 51, 179, &
|
||||||
|
6, 186, 198, &
|
||||||
|
79, 138, 197, &
|
||||||
|
1, 30, 122, &
|
||||||
|
1, 58, 162, &
|
||||||
|
2, 9, 172, &
|
||||||
|
3, 71, 161, &
|
||||||
|
4, 119, 142, &
|
||||||
|
5, 147, 160, &
|
||||||
|
6, 73, 183, &
|
||||||
|
7, 118, 202, &
|
||||||
|
8, 82, 98, &
|
||||||
|
2, 47, 56, &
|
||||||
|
10, 92, 151, &
|
||||||
|
11, 19, 150, &
|
||||||
|
12, 169, 179, &
|
||||||
|
13, 43, 188, &
|
||||||
|
14, 15, 192, &
|
||||||
|
14, 82, 120, &
|
||||||
|
16, 131, 155, &
|
||||||
|
17, 123, 148, &
|
||||||
|
18, 60, 117, &
|
||||||
|
11, 90, 134, &
|
||||||
|
20, 154, 195, &
|
||||||
|
21, 47, 166, &
|
||||||
|
22, 24, 86, &
|
||||||
|
23, 48, 167, &
|
||||||
|
21, 22, 190, &
|
||||||
|
25, 44, 53, &
|
||||||
|
26, 50, 64, &
|
||||||
|
4, 27, 95, &
|
||||||
|
28, 87, 205, &
|
||||||
|
1, 29, 183, &
|
||||||
|
30, 132, 185, &
|
||||||
|
31, 108, 180, &
|
||||||
|
32, 38, 174, &
|
||||||
|
33, 36, 128, &
|
||||||
|
34, 125, 134, &
|
||||||
|
35, 190, 201, &
|
||||||
|
30, 33, 142, &
|
||||||
|
37, 61, 81, &
|
||||||
|
32, 65, 70, &
|
||||||
|
39, 40, 41, &
|
||||||
|
36, 39, 78, &
|
||||||
|
40, 140, 144, &
|
||||||
|
42, 100, 194, &
|
||||||
|
9, 13, 111, &
|
||||||
|
20, 25, 115, &
|
||||||
|
45, 140, 165, &
|
||||||
|
10, 46, 60, &
|
||||||
|
15, 43, 200, &
|
||||||
|
23, 113, 158, &
|
||||||
|
16, 49, 150, &
|
||||||
|
12, 26, 164, &
|
||||||
|
51, 88, 115, &
|
||||||
|
52, 63, 141, &
|
||||||
|
44, 101, 187, &
|
||||||
|
34, 54, 173, &
|
||||||
|
55, 93, 139, &
|
||||||
|
56, 67, 102, &
|
||||||
|
57, 62, 152, &
|
||||||
|
29, 80, 89, &
|
||||||
|
5, 59, 195, &
|
||||||
|
18, 100, 156, &
|
||||||
|
28, 61, 162, &
|
||||||
|
31, 62, 163, &
|
||||||
|
38, 52, 103, &
|
||||||
|
50, 149, 175, &
|
||||||
|
65, 122, 138, &
|
||||||
|
66, 112, 171, &
|
||||||
|
24, 68, 198, &
|
||||||
|
68, 69, 84, &
|
||||||
|
51, 69, 108, &
|
||||||
|
70, 146, 159, &
|
||||||
|
3, 91, 201, &
|
||||||
|
72, 143, 149, &
|
||||||
|
6, 129, 188, &
|
||||||
|
74, 104, 153, &
|
||||||
|
54, 75, 186, &
|
||||||
|
76, 95, 200, &
|
||||||
|
77, 120, 168, &
|
||||||
|
41, 104, 182, &
|
||||||
|
79, 144, 187, &
|
||||||
|
58, 171, 193, &
|
||||||
|
37, 85, 135, &
|
||||||
|
8, 174, 197, &
|
||||||
|
83, 163, 176, &
|
||||||
|
53, 67, 184, &
|
||||||
|
85, 99, 196, &
|
||||||
|
76, 84, 138, &
|
||||||
|
77, 87, 194, &
|
||||||
|
86, 123, 202, &
|
||||||
|
57, 89, 146, &
|
||||||
|
27, 90, 97, &
|
||||||
|
91, 126, 136, &
|
||||||
|
46, 107, 113, &
|
||||||
|
55, 189, 204, &
|
||||||
|
94, 111, 130, &
|
||||||
|
19, 139, 152, &
|
||||||
|
96, 121, 158, &
|
||||||
|
75, 88, 94, &
|
||||||
|
93, 98, 157, &
|
||||||
|
79, 81, 203, &
|
||||||
|
42, 148, 206, &
|
||||||
|
101, 156, 181, &
|
||||||
|
97, 114, 154, &
|
||||||
|
103, 170, 175, &
|
||||||
|
78, 106, 191, &
|
||||||
|
105, 109, 135, &
|
||||||
|
64, 74, 176, &
|
||||||
|
73, 92, 169, &
|
||||||
|
80, 132, 181, &
|
||||||
|
71, 105, 186, &
|
||||||
|
110, 137, 204, &
|
||||||
|
21, 159, 192, &
|
||||||
|
35, 66, 137, &
|
||||||
|
48, 127, 205, &
|
||||||
|
114, 182, 193, &
|
||||||
|
2, 18, 163, &
|
||||||
|
59, 116, 129, &
|
||||||
|
99, 107, 119, &
|
||||||
|
7, 121, 125, &
|
||||||
|
102, 109, 141, &
|
||||||
|
19, 87, 160, &
|
||||||
|
96, 165, 172, &
|
||||||
|
63, 118, 147, &
|
||||||
|
17, 143, 196, &
|
||||||
|
124, 164, 173, &
|
||||||
|
112, 117, 131, &
|
||||||
|
52, 151, 180, &
|
||||||
|
127, 198, 199, &
|
||||||
|
106, 110, 167, &
|
||||||
|
116, 177, 178, &
|
||||||
|
72, 130, 155, &
|
||||||
|
49, 177, 203, &
|
||||||
|
128, 133, 166, &
|
||||||
|
133, 189, 206, &
|
||||||
|
75, 145, 191, &
|
||||||
|
1, 51, 133, &
|
||||||
|
83, 136, 168, &
|
||||||
|
4, 155, 179, &
|
||||||
|
3, 127, 157, &
|
||||||
|
90, 170, 190, &
|
||||||
|
5, 140, 164, &
|
||||||
|
6, 139, 196, &
|
||||||
|
31, 34, 142, &
|
||||||
|
7, 53, 104, &
|
||||||
|
11, 39, 109, &
|
||||||
|
145, 178, 197, &
|
||||||
|
25, 143, 146, &
|
||||||
|
8, 134, 181, &
|
||||||
|
9, 61, 174, &
|
||||||
|
10, 41, 198, &
|
||||||
|
12, 135, 159, &
|
||||||
|
14, 79, 113, &
|
||||||
|
13, 33, 66, &
|
||||||
|
153, 161, 188, &
|
||||||
|
16, 20, 136, &
|
||||||
|
17, 45, 180, &
|
||||||
|
22, 100, 116, &
|
||||||
|
15, 118, 191, &
|
||||||
|
157, 179, 184, &
|
||||||
|
37, 110, 185, &
|
||||||
|
30, 141, 168, &
|
||||||
|
27, 176, 189, &
|
||||||
|
28, 76, 186, &
|
||||||
|
24, 26, 111, &
|
||||||
|
124, 185, 199, &
|
||||||
|
45, 122, 126, &
|
||||||
|
35, 72, 147, &
|
||||||
|
32, 119, 194, &
|
||||||
|
36, 50, 138, &
|
||||||
|
23, 29, 175, &
|
||||||
|
42, 67, 124, &
|
||||||
|
40, 89, 94, &
|
||||||
|
43, 103, 199, &
|
||||||
|
49, 151, 167, &
|
||||||
|
44, 84, 204, &
|
||||||
|
47, 48, 122, &
|
||||||
|
46, 105, 195, &
|
||||||
|
55, 96, 177, &
|
||||||
|
57, 59, 106, &
|
||||||
|
38, 54, 193, &
|
||||||
|
58, 86, 152, &
|
||||||
|
63, 101, 162, &
|
||||||
|
60, 98, 123, &
|
||||||
|
64, 115, 205, &
|
||||||
|
62, 200, 201, &
|
||||||
|
65, 73, 154, &
|
||||||
|
56, 82, 183, &
|
||||||
|
69, 91, 99, &
|
||||||
|
70, 202, 203, &
|
||||||
|
74, 112, 197, &
|
||||||
|
71, 131, 206, &
|
||||||
|
77, 165, 171, &
|
||||||
|
68, 97, 120, &
|
||||||
|
78, 156, 161, &
|
||||||
|
80, 114, 148, &
|
||||||
|
83, 92, 187, &
|
||||||
|
88, 102, 158, &
|
||||||
|
107, 145, 166, &
|
||||||
|
122, 125, 130, &
|
||||||
|
85, 117, 170, &
|
||||||
|
121, 128, 169, &
|
||||||
|
126, 129, 173, &
|
||||||
|
153, 158, 160, &
|
||||||
|
93, 144, 149, &
|
||||||
|
88, 123, 137, &
|
||||||
|
81, 108, 182, &
|
||||||
|
132, 139, 192/
|
||||||
|
|
||||||
|
data Nm/ &
|
||||||
|
3, 74, 75, 103, 209, &
|
||||||
|
4, 76, 83, 189, 0, &
|
||||||
|
5, 77, 145, 212, 0, &
|
||||||
|
6, 78, 101, 211, 0, &
|
||||||
|
7, 79, 133, 214, 0, &
|
||||||
|
8, 72, 80, 147, 215, &
|
||||||
|
9, 81, 192, 217, 0, &
|
||||||
|
10, 82, 156, 221, 0, &
|
||||||
|
11, 76, 117, 222, 0, &
|
||||||
|
12, 84, 120, 223, 0, &
|
||||||
|
13, 85, 93, 218, 0, &
|
||||||
|
14, 86, 124, 224, 0, &
|
||||||
|
15, 87, 117, 226, 0, &
|
||||||
|
16, 88, 89, 225, 0, &
|
||||||
|
17, 88, 121, 231, 0, &
|
||||||
|
18, 90, 123, 228, 0, &
|
||||||
|
19, 91, 197, 229, 0, &
|
||||||
|
8, 92, 134, 189, 0, &
|
||||||
|
20, 85, 169, 194, 0, &
|
||||||
|
17, 94, 118, 228, 0, &
|
||||||
|
21, 95, 98, 185, 0, &
|
||||||
|
22, 96, 98, 230, 0, &
|
||||||
|
6, 97, 122, 243, 0, &
|
||||||
|
23, 96, 141, 237, 0, &
|
||||||
|
24, 99, 118, 220, 0, &
|
||||||
|
25, 100, 124, 237, 0, &
|
||||||
|
26, 101, 164, 235, 0, &
|
||||||
|
27, 69, 102, 135, 236, &
|
||||||
|
28, 103, 132, 243, 0, &
|
||||||
|
22, 74, 104, 110, 234, &
|
||||||
|
29, 105, 136, 216, 0, &
|
||||||
|
30, 106, 112, 241, 0, &
|
||||||
|
5, 70, 107, 110, 226, &
|
||||||
|
31, 108, 128, 216, 0, &
|
||||||
|
16, 109, 186, 240, 0, &
|
||||||
|
26, 107, 114, 242, 0, &
|
||||||
|
23, 111, 155, 233, 0, &
|
||||||
|
32, 106, 137, 253, 0, &
|
||||||
|
33, 113, 114, 218, 0, &
|
||||||
|
34, 113, 115, 245, 0, &
|
||||||
|
35, 113, 152, 223, 0, &
|
||||||
|
36, 116, 174, 244, 0, &
|
||||||
|
34, 87, 121, 246, 0, &
|
||||||
|
37, 99, 127, 248, 0, &
|
||||||
|
38, 119, 229, 239, 0, &
|
||||||
|
15, 71, 120, 166, 250, &
|
||||||
|
39, 83, 95, 249, 0, &
|
||||||
|
40, 97, 187, 249, 0, &
|
||||||
|
41, 123, 205, 247, 0, &
|
||||||
|
42, 100, 138, 242, 0, &
|
||||||
|
43, 71, 125, 143, 209, &
|
||||||
|
20, 126, 137, 200, 0, &
|
||||||
|
26, 99, 158, 217, 0, &
|
||||||
|
39, 128, 149, 253, 0, &
|
||||||
|
44, 129, 167, 251, 0, &
|
||||||
|
35, 83, 130, 260, 0, &
|
||||||
|
45, 131, 163, 252, 0, &
|
||||||
|
46, 75, 154, 254, 0, &
|
||||||
|
9, 133, 190, 252, 0, &
|
||||||
|
47, 92, 120, 256, 0, &
|
||||||
|
48, 111, 135, 222, 0, &
|
||||||
|
41, 131, 136, 258, 0, &
|
||||||
|
49, 126, 196, 255, 0, &
|
||||||
|
13, 100, 180, 257, 0, &
|
||||||
|
50, 112, 139, 259, 0, &
|
||||||
|
35, 140, 186, 226, 0, &
|
||||||
|
46, 130, 158, 244, 0, &
|
||||||
|
51, 70, 141, 142, 266, &
|
||||||
|
52, 142, 143, 261, 0, &
|
||||||
|
5, 112, 144, 262, 0, &
|
||||||
|
29, 77, 183, 264, 0, &
|
||||||
|
53, 146, 204, 240, 0, &
|
||||||
|
54, 80, 181, 259, 0, &
|
||||||
|
19, 63, 148, 180, 263, &
|
||||||
|
44, 149, 171, 208, 0, &
|
||||||
|
55, 150, 160, 236, 0, &
|
||||||
|
33, 151, 161, 265, 0, &
|
||||||
|
56, 114, 178, 267, 0, &
|
||||||
|
45, 73, 153, 173, 225, &
|
||||||
|
15, 132, 182, 268, 0, &
|
||||||
|
47, 111, 173, 279, 0, &
|
||||||
|
55, 82, 89, 260, 0, &
|
||||||
|
43, 157, 210, 269, 0, &
|
||||||
|
57, 142, 160, 248, 0, &
|
||||||
|
58, 155, 159, 273, 0, &
|
||||||
|
6, 96, 162, 254, 0, &
|
||||||
|
21, 102, 161, 194, 0, &
|
||||||
|
125, 171, 270, 278, 0, &
|
||||||
|
48, 132, 163, 245, 0, &
|
||||||
|
3, 93, 164, 213, 0, &
|
||||||
|
27, 145, 165, 261, 0, &
|
||||||
|
59, 84, 181, 269, 0, &
|
||||||
|
32, 129, 172, 277, 0, &
|
||||||
|
10, 168, 171, 245, 0, &
|
||||||
|
1, 54, 101, 150, 0, &
|
||||||
|
60, 170, 195, 251, 0, &
|
||||||
|
61, 164, 176, 266, 0, &
|
||||||
|
62, 82, 172, 256, 0, &
|
||||||
|
9, 159, 191, 261, 0, &
|
||||||
|
28, 116, 134, 230, 0, &
|
||||||
|
63, 127, 175, 255, 0, &
|
||||||
|
53, 130, 193, 270, 0, &
|
||||||
|
14, 137, 177, 246, 0, &
|
||||||
|
50, 148, 152, 217, 0, &
|
||||||
|
38, 179, 183, 250, 0, &
|
||||||
|
30, 178, 202, 252, 0, &
|
||||||
|
24, 166, 191, 271, 0, &
|
||||||
|
54, 105, 143, 279, 0, &
|
||||||
|
28, 179, 193, 218, 0, &
|
||||||
|
8, 61, 184, 202, 233, &
|
||||||
|
64, 117, 168, 237, 0, &
|
||||||
|
56, 140, 199, 263, 0, &
|
||||||
|
65, 122, 166, 225, 0, &
|
||||||
|
25, 176, 188, 268, 0, &
|
||||||
|
36, 118, 125, 257, 0, &
|
||||||
|
66, 190, 203, 230, 0, &
|
||||||
|
40, 92, 199, 273, 0, &
|
||||||
|
64, 81, 196, 231, 0, &
|
||||||
|
49, 78, 191, 241, 0, &
|
||||||
|
40, 89, 151, 266, 0, &
|
||||||
|
61, 170, 192, 274, 0, &
|
||||||
|
74, 139, 239, 249, 272, &
|
||||||
|
91, 162, 256, 278, 0, &
|
||||||
|
10, 198, 238, 244, 0, &
|
||||||
|
67, 108, 192, 272, 0, &
|
||||||
|
23, 165, 239, 275, 0, &
|
||||||
|
7, 187, 201, 212, 0, &
|
||||||
|
38, 107, 206, 274, 0, &
|
||||||
|
53, 147, 190, 275, 0, &
|
||||||
|
65, 168, 204, 272, 0, &
|
||||||
|
60, 90, 199, 264, 0, &
|
||||||
|
59, 104, 182, 280, 0, &
|
||||||
|
62, 206, 207, 209, 0, &
|
||||||
|
52, 93, 108, 221, 0, &
|
||||||
|
68, 155, 179, 224, 0, &
|
||||||
|
32, 165, 210, 228, 0, &
|
||||||
|
69, 184, 186, 278, 0, &
|
||||||
|
58, 73, 139, 160, 242, &
|
||||||
|
129, 169, 215, 280, 0, &
|
||||||
|
69, 115, 119, 214, 0, &
|
||||||
|
57, 126, 193, 234, 0, &
|
||||||
|
68, 78, 110, 216, 0, &
|
||||||
|
4, 146, 197, 220, 0, &
|
||||||
|
22, 115, 153, 277, 0, &
|
||||||
|
59, 208, 219, 271, 0, &
|
||||||
|
55, 144, 163, 220, 0, &
|
||||||
|
43, 79, 196, 240, 0, &
|
||||||
|
68, 91, 174, 268, 0, &
|
||||||
|
51, 138, 146, 277, 0, &
|
||||||
|
1, 70, 85, 123, 0, &
|
||||||
|
36, 84, 200, 247, 0, &
|
||||||
|
50, 131, 169, 254, 0, &
|
||||||
|
62, 148, 227, 276, 0, &
|
||||||
|
2, 94, 176, 259, 0, &
|
||||||
|
37, 90, 204, 211, 0, &
|
||||||
|
14, 134, 175, 267, 0, &
|
||||||
|
58, 172, 212, 232, 0, &
|
||||||
|
122, 170, 270, 276, 0, &
|
||||||
|
46, 144, 185, 224, 0, &
|
||||||
|
31, 79, 194, 276, 0, &
|
||||||
|
57, 77, 227, 267, 0, &
|
||||||
|
18, 75, 135, 255, 0, &
|
||||||
|
65, 136, 157, 189, 0, &
|
||||||
|
3, 124, 198, 214, 0, &
|
||||||
|
12, 119, 195, 265, 0, &
|
||||||
|
13, 95, 206, 271, 0, &
|
||||||
|
52, 97, 202, 247, 0, &
|
||||||
|
11, 151, 210, 234, 0, &
|
||||||
|
27, 86, 181, 274, 0, &
|
||||||
|
44, 177, 213, 273, 0, &
|
||||||
|
24, 140, 154, 265, 0, &
|
||||||
|
1, 16, 76, 195, 0, &
|
||||||
|
56, 128, 198, 275, 0, &
|
||||||
|
7, 106, 156, 222, 0, &
|
||||||
|
12, 138, 177, 243, 0, &
|
||||||
|
66, 157, 180, 235, 0, &
|
||||||
|
34, 203, 205, 251, 0, &
|
||||||
|
2, 20, 203, 219, 0, &
|
||||||
|
71, 86, 211, 232, 0, &
|
||||||
|
37, 105, 200, 229, 0, &
|
||||||
|
60, 175, 182, 221, 0, &
|
||||||
|
21, 152, 188, 279, 0, &
|
||||||
|
41, 64, 80, 103, 260, &
|
||||||
|
2, 48, 158, 232, 0, &
|
||||||
|
42, 104, 233, 238, 0, &
|
||||||
|
72, 149, 183, 236, 0, &
|
||||||
|
25, 127, 153, 269, 0, &
|
||||||
|
18, 67, 87, 147, 227, &
|
||||||
|
17, 167, 207, 235, 0, &
|
||||||
|
30, 98, 109, 213, 0, &
|
||||||
|
51, 178, 208, 231, 0, &
|
||||||
|
29, 88, 185, 280, 0, &
|
||||||
|
66, 154, 188, 253, 0, &
|
||||||
|
67, 116, 161, 241, 0, &
|
||||||
|
63, 94, 133, 250, 0, &
|
||||||
|
33, 159, 197, 215, 0, &
|
||||||
|
73, 156, 219, 263, 0, &
|
||||||
|
49, 72, 141, 201, 223, &
|
||||||
|
4, 201, 238, 246, 0, &
|
||||||
|
19, 121, 150, 258, 0, &
|
||||||
|
47, 109, 145, 258, 0, &
|
||||||
|
42, 81, 162, 262, 0, &
|
||||||
|
39, 173, 205, 262, 0, &
|
||||||
|
31, 167, 184, 248, 0, &
|
||||||
|
45, 102, 187, 257, 0, &
|
||||||
|
11, 174, 207, 264, 0/
|
||||||
|
|
||||||
|
data nrw/ &
|
||||||
|
5,4,4,4,4,5,4,4,4,4,4,4,4,4,4,4,4,4,4,4, &
|
||||||
|
4,4,4,4,4,4,4,5,4,5,4,4,5,4,4,4,4,4,4,4, &
|
||||||
|
4,4,4,4,4,5,4,4,4,4,5,4,4,4,4,4,4,4,4,4, &
|
||||||
|
4,4,4,4,4,4,4,5,4,4,4,4,4,5,4,4,4,4,5,4, &
|
||||||
|
4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4, &
|
||||||
|
4,4,4,4,4,4,4,4,4,5,4,4,4,4,4,4,4,4,4,4, &
|
||||||
|
4,5,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,5,4,4, &
|
||||||
|
4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4, &
|
||||||
|
4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4, &
|
||||||
|
4,4,5,4,4,4,4,5,4,4,4,4,4,4,4,4,4,5,4,4, &
|
||||||
|
4,4,4,4,4,4/
|
||||||
|
|
||||||
|
ncw=3
|
139
lib/fst280/ldpcsim280_101.f90
Normal file
139
lib/fst280/ldpcsim280_101.f90
Normal file
@ -0,0 +1,139 @@
|
|||||||
|
program ldpcsim280_101
|
||||||
|
|
||||||
|
! End-to-end test of the (280,101)/crc24 encoder and decoders.
|
||||||
|
|
||||||
|
use packjt77
|
||||||
|
|
||||||
|
parameter(N=280, K=101, M=N-K)
|
||||||
|
character*8 arg
|
||||||
|
character*37 msg0,msg
|
||||||
|
character*77 c77
|
||||||
|
character*24 c24
|
||||||
|
integer*1 msgbits(101)
|
||||||
|
integer*1 apmask(280)
|
||||||
|
integer*1 cw(280)
|
||||||
|
integer*1 codeword(N),message101(101)
|
||||||
|
integer ncrc24
|
||||||
|
real rxdata(N),llr(N)
|
||||||
|
real llrd(280)
|
||||||
|
logical first,unpk77_success
|
||||||
|
data first/.true./
|
||||||
|
|
||||||
|
nargs=iargc()
|
||||||
|
if(nargs.ne.6 .and. nargs.ne.7) then
|
||||||
|
print*,'Usage : ldpcsim niter norder maxosd #trials s K [msg]'
|
||||||
|
print*,'e.g. ldpcsim280_101 20 3 2 1000 0.85 91 "K9AN K1JT FN20"'
|
||||||
|
print*,'s : if negative, then value is ignored and sigma is calculated from SNR.'
|
||||||
|
print*,'niter : is the number of BP iterations.'
|
||||||
|
print*,'norder: -1 is BP only, norder>=0 is OSD order'
|
||||||
|
print*,'K :is the number of message+CRC bits and must be in the range [77,101]'
|
||||||
|
print*,'WSPR-format message is optional'
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
call getarg(1,arg)
|
||||||
|
read(arg,*) max_iterations
|
||||||
|
call getarg(2,arg)
|
||||||
|
read(arg,*) norder
|
||||||
|
call getarg(3,arg)
|
||||||
|
read(arg,*) maxosd
|
||||||
|
call getarg(4,arg)
|
||||||
|
read(arg,*) ntrials
|
||||||
|
call getarg(5,arg)
|
||||||
|
read(arg,*) s
|
||||||
|
call getarg(6,arg)
|
||||||
|
read(arg,*) Keff
|
||||||
|
msg0='K9AN K1JT FN20 '
|
||||||
|
if(nargs.eq.7) call getarg(7,msg0)
|
||||||
|
call pack77(msg0,i3,n3,c77)
|
||||||
|
call unpack77(c77,0,msg,unpk77_success)
|
||||||
|
if(unpk77_success) then
|
||||||
|
write(*,1100) msg(1:37)
|
||||||
|
1100 format('Decoded message: ',a37)
|
||||||
|
else
|
||||||
|
print*,'Error unpacking message'
|
||||||
|
endif
|
||||||
|
|
||||||
|
rate=real(91)/real(N)
|
||||||
|
|
||||||
|
write(*,*) "code rate: ",rate
|
||||||
|
write(*,*) "niter : ",max_iterations
|
||||||
|
write(*,*) "norder : ",norder
|
||||||
|
write(*,*) "s : ",s
|
||||||
|
write(*,*) "K : ",Keff
|
||||||
|
|
||||||
|
msgbits=0
|
||||||
|
read(c77,'(77i1)') msgbits(1:77)
|
||||||
|
write(*,*) 'message'
|
||||||
|
write(*,'(77i1)') msgbits(1:77)
|
||||||
|
|
||||||
|
call get_crc24(msgbits,101,ncrc24)
|
||||||
|
write(c24,'(b24.24)') ncrc24
|
||||||
|
read(c24,'(24i1)') msgbits(78:101)
|
||||||
|
write(*,*) 'message with crc24'
|
||||||
|
write(*,'(101i1)') msgbits(1:101)
|
||||||
|
call encode280_101(msgbits,codeword)
|
||||||
|
call init_random_seed()
|
||||||
|
call sgran()
|
||||||
|
|
||||||
|
write(*,*) 'codeword'
|
||||||
|
write(*,'(77i1,1x,24i1,1x,73i1)') codeword
|
||||||
|
|
||||||
|
write(*,*) "Eb/N0 Es/N0 ngood nundetected sigma symbol error rate"
|
||||||
|
do idb = 8,-3,-1
|
||||||
|
db=idb/2.0-1.0
|
||||||
|
sigma=1/sqrt( 2*rate*(10**(db/10.0)) ) ! to make db represent Eb/No
|
||||||
|
! sigma=1/sqrt( 2*(10**(db/10.0)) ) ! db represents Es/No
|
||||||
|
ngood=0
|
||||||
|
nue=0
|
||||||
|
nberr=0
|
||||||
|
do itrial=1, ntrials
|
||||||
|
! Create a realization of a noisy received word
|
||||||
|
do i=1,N
|
||||||
|
rxdata(i) = 2.0*codeword(i)-1.0 + sigma*gran()
|
||||||
|
enddo
|
||||||
|
nerr=0
|
||||||
|
do i=1,N
|
||||||
|
if( rxdata(i)*(2*codeword(i)-1.0) .lt. 0 ) nerr=nerr+1
|
||||||
|
enddo
|
||||||
|
nberr=nberr+nerr
|
||||||
|
|
||||||
|
rxav=sum(rxdata)/N
|
||||||
|
rx2av=sum(rxdata*rxdata)/N
|
||||||
|
rxsig=sqrt(rx2av-rxav*rxav)
|
||||||
|
rxdata=rxdata/rxsig
|
||||||
|
if( s .lt. 0 ) then
|
||||||
|
ss=sigma
|
||||||
|
else
|
||||||
|
ss=s
|
||||||
|
endif
|
||||||
|
|
||||||
|
llr=2.0*rxdata/(ss*ss)
|
||||||
|
apmask=0
|
||||||
|
! max_iterations is max number of belief propagation iterations
|
||||||
|
call bpdecode280_101(llr,apmask,max_iterations,message101,cw,nharderror,niterations,nchecks)
|
||||||
|
dmin=0.0
|
||||||
|
if( (nharderror .lt. 0) .and. (norder .ge. 0) ) then
|
||||||
|
! call osd280_101(llr, Keff, apmask, norder, message101, cw, nharderror, dmin)
|
||||||
|
call decode280_101(llr, Keff, maxosd, norder, apmask, message101, cw, ntype, nharderror, dmin)
|
||||||
|
endif
|
||||||
|
|
||||||
|
if(nharderror.ge.0) then
|
||||||
|
n2err=0
|
||||||
|
do i=1,N
|
||||||
|
if( cw(i)*(2*codeword(i)-1.0) .lt. 0 ) n2err=n2err+1
|
||||||
|
enddo
|
||||||
|
if(n2err.eq.0) then
|
||||||
|
ngood=ngood+1
|
||||||
|
else
|
||||||
|
nue=nue+1
|
||||||
|
endif
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
! snr2500=db+10*log10(200.0/116.0/2500.0)
|
||||||
|
esn0=db+10*log10(rate)
|
||||||
|
pberr=real(nberr)/(real(ntrials*N))
|
||||||
|
write(*,"(f4.1,4x,f5.1,1x,i8,1x,i8,8x,f5.2,8x,e10.3)") db,esn0,ngood,nue,ss,pberr
|
||||||
|
|
||||||
|
enddo
|
||||||
|
|
||||||
|
end program ldpcsim280_101
|
132
lib/fst280/ldpcsim280_74.f90
Normal file
132
lib/fst280/ldpcsim280_74.f90
Normal file
@ -0,0 +1,132 @@
|
|||||||
|
program ldpcsim280_74
|
||||||
|
|
||||||
|
! End-to-end test of the (280,74)/crc24 encoder and decoders.
|
||||||
|
|
||||||
|
use packjt77
|
||||||
|
|
||||||
|
parameter(N=280, K=74, M=N-K)
|
||||||
|
character*8 arg
|
||||||
|
character*37 msg0,msg
|
||||||
|
character*77 c77
|
||||||
|
character*24 c24
|
||||||
|
integer*1 msgbits(74)
|
||||||
|
integer*1 apmask(280)
|
||||||
|
integer*1 cw(280)
|
||||||
|
integer*1 codeword(N),message74(74)
|
||||||
|
integer ncrc24
|
||||||
|
real rxdata(N),llr(N)
|
||||||
|
real llrd(280)
|
||||||
|
logical first,unpk77_success
|
||||||
|
data first/.true./
|
||||||
|
|
||||||
|
nargs=iargc()
|
||||||
|
if(nargs.ne.5 .and. nargs.ne.6) then
|
||||||
|
print*,'Usage: ldpcsim norder maxosd #trials s K [msg]'
|
||||||
|
print*,'e.g. ldpcsim280_74 3 2 1000 0.85 91 "K9AN K1JT FN20"'
|
||||||
|
print*,'s : if negative, then value is ignored and sigma is calculated from SNR.'
|
||||||
|
print*,'niter: is the number of BP iterations.'
|
||||||
|
print*,'norder: -1 is BP only, norder>=0 is OSD order'
|
||||||
|
print*,'maxosd: number of calls to OSD'
|
||||||
|
print*,'K :is the number of message+CRC bits and must be in the range [50,74]'
|
||||||
|
print*,'WSPR-format message is optional'
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
call getarg(1,arg)
|
||||||
|
read(arg,*) norder
|
||||||
|
call getarg(2,arg)
|
||||||
|
read(arg,*) maxosd
|
||||||
|
call getarg(3,arg)
|
||||||
|
read(arg,*) ntrials
|
||||||
|
call getarg(4,arg)
|
||||||
|
read(arg,*) s
|
||||||
|
call getarg(5,arg)
|
||||||
|
read(arg,*) Keff
|
||||||
|
msg0='K9AN K1JT FN20 '
|
||||||
|
if(nargs.eq.6) call getarg(6,msg0)
|
||||||
|
call pack77(msg0,i3,n3,c77)
|
||||||
|
call unpack77(c77,0,msg,unpk77_success)
|
||||||
|
if(unpk77_success) then
|
||||||
|
write(*,1100) msg(1:37)
|
||||||
|
1100 format('Decoded message: ',a37)
|
||||||
|
else
|
||||||
|
print*,'Error unpacking message'
|
||||||
|
endif
|
||||||
|
|
||||||
|
rate=real(64)/real(N)
|
||||||
|
|
||||||
|
write(*,*) "code rate: ",rate
|
||||||
|
write(*,*) "norder : ",norder
|
||||||
|
write(*,*) "s : ",s
|
||||||
|
write(*,*) "K : ",Keff
|
||||||
|
|
||||||
|
msgbits=0
|
||||||
|
read(c77,'(50i1)') msgbits(1:50)
|
||||||
|
write(*,*) 'message'
|
||||||
|
write(*,'(50i1)') msgbits(1:50)
|
||||||
|
|
||||||
|
msgbits(51:74)=0
|
||||||
|
call get_crc24(msgbits,74,ncrc24)
|
||||||
|
write(c24,'(b24.24)') ncrc24
|
||||||
|
read(c24,'(24i1)') msgbits(51:74)
|
||||||
|
write(*,*) 'message with crc24'
|
||||||
|
write(*,'(74i1)') msgbits(1:74)
|
||||||
|
call encode280_74(msgbits,codeword)
|
||||||
|
call init_random_seed()
|
||||||
|
call sgran()
|
||||||
|
|
||||||
|
write(*,*) 'codeword'
|
||||||
|
write(*,'(50i1,1x,24i1,1x,206i1)') codeword
|
||||||
|
|
||||||
|
write(*,*) "Eb/N0 Es/N0 ngood nundetected sigma symbol error rate"
|
||||||
|
do idb = 2,-2,-1
|
||||||
|
db=idb/2.0-1.0
|
||||||
|
sigma=1/sqrt( 2*rate*(10**(db/10.0)) ) ! to make db represent Eb/No
|
||||||
|
! sigma=1/sqrt( 2*(10**(db/10.0)) ) ! db represents Es/No
|
||||||
|
ngood=0
|
||||||
|
nue=0
|
||||||
|
nberr=0
|
||||||
|
do itrial=1, ntrials
|
||||||
|
! Create a realization of a noisy received word
|
||||||
|
do i=1,N
|
||||||
|
rxdata(i) = 2.0*codeword(i)-1.0 + sigma*gran()
|
||||||
|
enddo
|
||||||
|
nerr=0
|
||||||
|
do i=1,N
|
||||||
|
if( rxdata(i)*(2*codeword(i)-1.0) .lt. 0 ) nerr=nerr+1
|
||||||
|
enddo
|
||||||
|
nberr=nberr+nerr
|
||||||
|
|
||||||
|
rxav=sum(rxdata)/N
|
||||||
|
rx2av=sum(rxdata*rxdata)/N
|
||||||
|
rxsig=sqrt(rx2av-rxav*rxav)
|
||||||
|
rxdata=rxdata/rxsig
|
||||||
|
if( s .lt. 0 ) then
|
||||||
|
ss=sigma
|
||||||
|
else
|
||||||
|
ss=s
|
||||||
|
endif
|
||||||
|
|
||||||
|
llr=2.0*rxdata/(ss*ss)
|
||||||
|
apmask=0
|
||||||
|
call decode280_74(llr,Keff,maxosd,norder,apmask,message74,cw,ntype,nharderror,dmin)
|
||||||
|
|
||||||
|
if(nharderror.ge.0) then
|
||||||
|
n2err=0
|
||||||
|
do i=1,N
|
||||||
|
if( cw(i)*(2*codeword(i)-1.0) .lt. 0 ) n2err=n2err+1
|
||||||
|
enddo
|
||||||
|
if(n2err.eq.0) then
|
||||||
|
ngood=ngood+1
|
||||||
|
else
|
||||||
|
nue=nue+1
|
||||||
|
endif
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
! snr2500=db+10*log10(200.0/116.0/2500.0)
|
||||||
|
esn0=db+10*log10(rate)
|
||||||
|
pberr=real(nberr)/(real(ntrials*N))
|
||||||
|
write(*,"(f4.1,4x,f5.1,1x,i8,1x,i8,8x,f5.2,8x,e10.3)") db,esn0,ngood,nue,ss,pberr
|
||||||
|
|
||||||
|
enddo
|
||||||
|
|
||||||
|
end program ldpcsim280_74
|
403
lib/fst280/osd280_101.f90
Normal file
403
lib/fst280/osd280_101.f90
Normal file
@ -0,0 +1,403 @@
|
|||||||
|
subroutine osd280_101(llr,k,apmask,ndeep,message101,cw,nhardmin,dmin)
|
||||||
|
!
|
||||||
|
! An ordered-statistics decoder for the (280,101) code.
|
||||||
|
! Message payload is 77 bits. Any or all of a 24-bit CRC can be
|
||||||
|
! used for detecting incorrect codewords. The remaining CRC bits are
|
||||||
|
! cascaded with the LDPC code for the purpose of improving the
|
||||||
|
! distance spectrum of the code.
|
||||||
|
!
|
||||||
|
! If p1 (0.le.p1.le.24) is the number of CRC24 bits that are
|
||||||
|
! to be used for bad codeword detection, then the argument k should
|
||||||
|
! be set to 77+p1.
|
||||||
|
!
|
||||||
|
! Valid values for k are in the range [77,101].
|
||||||
|
!
|
||||||
|
character*24 c24
|
||||||
|
integer, parameter:: N=280
|
||||||
|
integer*1 apmask(N),apmaskr(N)
|
||||||
|
integer*1, allocatable, save :: gen(:,:)
|
||||||
|
integer*1, allocatable :: genmrb(:,:),g2(:,:)
|
||||||
|
integer*1, allocatable :: temp(:),m0(:),me(:),mi(:),misub(:),e2sub(:),e2(:),ui(:)
|
||||||
|
integer*1, allocatable :: r2pat(:)
|
||||||
|
integer indices(N),nxor(N)
|
||||||
|
integer*1 cw(N),ce(N),c0(N),hdec(N)
|
||||||
|
integer*1, allocatable :: decoded(:)
|
||||||
|
integer*1 message101(101)
|
||||||
|
integer indx(N)
|
||||||
|
real llr(N),rx(N),absrx(N)
|
||||||
|
|
||||||
|
logical first,reset
|
||||||
|
data first/.true./
|
||||||
|
save first
|
||||||
|
|
||||||
|
allocate( genmrb(k,N), g2(N,k) )
|
||||||
|
allocate( temp(k), m0(k), me(k), mi(k), misub(k), e2sub(N-k), e2(N-k), ui(N-k) )
|
||||||
|
allocate( r2pat(N-k), decoded(k) )
|
||||||
|
|
||||||
|
if( first ) then ! fill the generator matrix
|
||||||
|
!
|
||||||
|
! Create generator matrix for partial CRC cascaded with LDPC code.
|
||||||
|
!
|
||||||
|
! Let p2=101-k and p1+p2=24.
|
||||||
|
!
|
||||||
|
! The last p2 bits of the CRC24 are cascaded with the LDPC code.
|
||||||
|
!
|
||||||
|
! The first p1=k-77 CRC24 bits will be used for error detection.
|
||||||
|
!
|
||||||
|
allocate( gen(k,N) )
|
||||||
|
gen=0
|
||||||
|
do i=1,k
|
||||||
|
message101=0
|
||||||
|
message101(i)=1
|
||||||
|
if(i.le.77) then
|
||||||
|
call get_crc24(message101,101,ncrc24)
|
||||||
|
write(c24,'(b24.24)') ncrc24
|
||||||
|
read(c24,'(24i1)') message101(78:101)
|
||||||
|
message101(78:k)=0
|
||||||
|
endif
|
||||||
|
call encode280_101(message101,cw)
|
||||||
|
gen(i,:)=cw
|
||||||
|
enddo
|
||||||
|
|
||||||
|
first=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
rx=llr
|
||||||
|
apmaskr=apmask
|
||||||
|
|
||||||
|
! Hard decisions on the received word.
|
||||||
|
hdec=0
|
||||||
|
where(rx .ge. 0) hdec=1
|
||||||
|
|
||||||
|
! Use magnitude of received symbols as a measure of reliability.
|
||||||
|
absrx=abs(rx)
|
||||||
|
call indexx(absrx,N,indx)
|
||||||
|
|
||||||
|
! Re-order the columns of the generator matrix in order of decreasing reliability.
|
||||||
|
do i=1,N
|
||||||
|
genmrb(1:k,i)=gen(1:k,indx(N+1-i))
|
||||||
|
indices(i)=indx(N+1-i)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
! Do gaussian elimination to create a generator matrix with the most reliable
|
||||||
|
! received bits in positions 1:k in order of decreasing reliability (more or less).
|
||||||
|
do id=1,k ! diagonal element indices
|
||||||
|
do icol=id,k+20 ! The 20 is ad hoc - beware
|
||||||
|
iflag=0
|
||||||
|
if( genmrb(id,icol) .eq. 1 ) then
|
||||||
|
iflag=1
|
||||||
|
if( icol .ne. id ) then ! reorder column
|
||||||
|
temp(1:k)=genmrb(1:k,id)
|
||||||
|
genmrb(1:k,id)=genmrb(1:k,icol)
|
||||||
|
genmrb(1:k,icol)=temp(1:k)
|
||||||
|
itmp=indices(id)
|
||||||
|
indices(id)=indices(icol)
|
||||||
|
indices(icol)=itmp
|
||||||
|
endif
|
||||||
|
do ii=1,k
|
||||||
|
if( ii .ne. id .and. genmrb(ii,id) .eq. 1 ) then
|
||||||
|
genmrb(ii,1:N)=ieor(genmrb(ii,1:N),genmrb(id,1:N))
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
exit
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
g2=transpose(genmrb)
|
||||||
|
|
||||||
|
! The hard decisions for the k MRB bits define the order 0 message, m0.
|
||||||
|
! Encode m0 using the modified generator matrix to find the "order 0" codeword.
|
||||||
|
! Flip various combinations of bits in m0 and re-encode to generate a list of
|
||||||
|
! codewords. Return the member of the list that has the smallest Euclidean
|
||||||
|
! distance to the received word.
|
||||||
|
|
||||||
|
hdec=hdec(indices) ! hard decisions from received symbols
|
||||||
|
m0=hdec(1:k) ! zero'th order message
|
||||||
|
absrx=absrx(indices)
|
||||||
|
rx=rx(indices)
|
||||||
|
apmaskr=apmaskr(indices)
|
||||||
|
|
||||||
|
call mrbencode101(m0,c0,g2,N,k)
|
||||||
|
nxor=ieor(c0,hdec)
|
||||||
|
nhardmin=sum(nxor)
|
||||||
|
dmin=sum(nxor*absrx)
|
||||||
|
|
||||||
|
cw=c0
|
||||||
|
ntotal=0
|
||||||
|
nrejected=0
|
||||||
|
npre1=0
|
||||||
|
npre2=0
|
||||||
|
|
||||||
|
if(ndeep.eq.0) goto 998 ! norder=0
|
||||||
|
if(ndeep.gt.6) ndeep=6
|
||||||
|
if( ndeep.eq. 1) then
|
||||||
|
nord=1
|
||||||
|
npre1=0
|
||||||
|
npre2=0
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
elseif(ndeep.eq.2) then
|
||||||
|
nord=1
|
||||||
|
npre1=1
|
||||||
|
npre2=0
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
elseif(ndeep.eq.3) then
|
||||||
|
nord=1
|
||||||
|
npre1=1
|
||||||
|
npre2=1
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
ntau=14
|
||||||
|
elseif(ndeep.eq.4) then
|
||||||
|
nord=2
|
||||||
|
npre1=1
|
||||||
|
npre2=1
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
ntau=17
|
||||||
|
elseif(ndeep.eq.5) then
|
||||||
|
nord=3
|
||||||
|
npre1=1
|
||||||
|
npre2=1
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
ntau=15
|
||||||
|
elseif(ndeep.eq.6) then
|
||||||
|
nord=4
|
||||||
|
npre1=1
|
||||||
|
npre2=1
|
||||||
|
nt=95
|
||||||
|
ntheta=12
|
||||||
|
ntau=15
|
||||||
|
endif
|
||||||
|
|
||||||
|
do iorder=1,nord
|
||||||
|
misub(1:k-iorder)=0
|
||||||
|
misub(k-iorder+1:k)=1
|
||||||
|
iflag=k-iorder+1
|
||||||
|
do while(iflag .ge.0)
|
||||||
|
if(iorder.eq.nord .and. npre1.eq.0) then
|
||||||
|
iend=iflag
|
||||||
|
else
|
||||||
|
iend=1
|
||||||
|
endif
|
||||||
|
d1=0.
|
||||||
|
do n1=iflag,iend,-1
|
||||||
|
mi=misub
|
||||||
|
mi(n1)=1
|
||||||
|
if(any(iand(apmaskr(1:k),mi).eq.1)) cycle
|
||||||
|
ntotal=ntotal+1
|
||||||
|
me=ieor(m0,mi)
|
||||||
|
if(n1.eq.iflag) then
|
||||||
|
call mrbencode101(me,ce,g2,N,k)
|
||||||
|
e2sub=ieor(ce(k+1:N),hdec(k+1:N))
|
||||||
|
e2=e2sub
|
||||||
|
nd1kpt=sum(e2sub(1:nt))+1
|
||||||
|
d1=sum(ieor(me(1:k),hdec(1:k))*absrx(1:k))
|
||||||
|
else
|
||||||
|
e2=ieor(e2sub,g2(k+1:N,n1))
|
||||||
|
nd1kpt=sum(e2(1:nt))+2
|
||||||
|
endif
|
||||||
|
if(nd1kpt .le. ntheta) then
|
||||||
|
call mrbencode101(me,ce,g2,N,k)
|
||||||
|
nxor=ieor(ce,hdec)
|
||||||
|
if(n1.eq.iflag) then
|
||||||
|
dd=d1+sum(e2sub*absrx(k+1:N))
|
||||||
|
else
|
||||||
|
dd=d1+ieor(ce(n1),hdec(n1))*absrx(n1)+sum(e2*absrx(k+1:N))
|
||||||
|
endif
|
||||||
|
if( dd .lt. dmin ) then
|
||||||
|
dmin=dd
|
||||||
|
cw=ce
|
||||||
|
nhardmin=sum(nxor)
|
||||||
|
nd1kptbest=nd1kpt
|
||||||
|
endif
|
||||||
|
else
|
||||||
|
nrejected=nrejected+1
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
! Get the next test error pattern, iflag will go negative
|
||||||
|
! when the last pattern with weight iorder has been generated.
|
||||||
|
call nextpat101(misub,k,iorder,iflag)
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
if(npre2.eq.1) then
|
||||||
|
reset=.true.
|
||||||
|
ntotal=0
|
||||||
|
do i1=k,1,-1
|
||||||
|
do i2=i1-1,1,-1
|
||||||
|
ntotal=ntotal+1
|
||||||
|
mi(1:ntau)=ieor(g2(k+1:k+ntau,i1),g2(k+1:k+ntau,i2))
|
||||||
|
call boxit101(reset,mi(1:ntau),ntau,ntotal,i1,i2)
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ncount2=0
|
||||||
|
ntotal2=0
|
||||||
|
reset=.true.
|
||||||
|
! Now run through again and do the second pre-processing rule
|
||||||
|
misub(1:k-nord)=0
|
||||||
|
misub(k-nord+1:k)=1
|
||||||
|
iflag=k-nord+1
|
||||||
|
do while(iflag .ge.0)
|
||||||
|
me=ieor(m0,misub)
|
||||||
|
call mrbencode101(me,ce,g2,N,k)
|
||||||
|
e2sub=ieor(ce(k+1:N),hdec(k+1:N))
|
||||||
|
do i2=0,ntau
|
||||||
|
ntotal2=ntotal2+1
|
||||||
|
ui=0
|
||||||
|
if(i2.gt.0) ui(i2)=1
|
||||||
|
r2pat=ieor(e2sub,ui)
|
||||||
|
778 continue
|
||||||
|
call fetchit101(reset,r2pat(1:ntau),ntau,in1,in2)
|
||||||
|
if(in1.gt.0.and.in2.gt.0) then
|
||||||
|
ncount2=ncount2+1
|
||||||
|
mi=misub
|
||||||
|
mi(in1)=1
|
||||||
|
mi(in2)=1
|
||||||
|
if(sum(mi).lt.nord+npre1+npre2.or.any(iand(apmaskr(1:k),mi).eq.1)) cycle
|
||||||
|
me=ieor(m0,mi)
|
||||||
|
call mrbencode101(me,ce,g2,N,k)
|
||||||
|
nxor=ieor(ce,hdec)
|
||||||
|
dd=sum(nxor*absrx)
|
||||||
|
if( dd .lt. dmin ) then
|
||||||
|
dmin=dd
|
||||||
|
cw=ce
|
||||||
|
nhardmin=sum(nxor)
|
||||||
|
endif
|
||||||
|
goto 778
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
call nextpat101(misub,k,nord,iflag)
|
||||||
|
enddo
|
||||||
|
endif
|
||||||
|
|
||||||
|
998 continue
|
||||||
|
! Re-order the codeword to [message bits][parity bits] format.
|
||||||
|
cw(indices)=cw
|
||||||
|
hdec(indices)=hdec
|
||||||
|
message101=cw(1:101)
|
||||||
|
call get_crc24(message101,101,nbadcrc)
|
||||||
|
if(nbadcrc.ne.0) nhardmin=-nhardmin
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine osd280_101
|
||||||
|
|
||||||
|
subroutine mrbencode101(me,codeword,g2,N,K)
|
||||||
|
integer*1 me(K),codeword(N),g2(N,K)
|
||||||
|
! fast encoding for low-weight test patterns
|
||||||
|
codeword=0
|
||||||
|
do i=1,K
|
||||||
|
if( me(i) .eq. 1 ) then
|
||||||
|
codeword=ieor(codeword,g2(1:N,i))
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
return
|
||||||
|
end subroutine mrbencode101
|
||||||
|
|
||||||
|
subroutine nextpat101(mi,k,iorder,iflag)
|
||||||
|
integer*1 mi(k),ms(k)
|
||||||
|
! generate the next test error pattern
|
||||||
|
ind=-1
|
||||||
|
do i=1,k-1
|
||||||
|
if( mi(i).eq.0 .and. mi(i+1).eq.1) ind=i
|
||||||
|
enddo
|
||||||
|
if( ind .lt. 0 ) then ! no more patterns of this order
|
||||||
|
iflag=ind
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
ms=0
|
||||||
|
ms(1:ind-1)=mi(1:ind-1)
|
||||||
|
ms(ind)=1
|
||||||
|
ms(ind+1)=0
|
||||||
|
if( ind+1 .lt. k ) then
|
||||||
|
nz=iorder-sum(ms)
|
||||||
|
ms(k-nz+1:k)=1
|
||||||
|
endif
|
||||||
|
mi=ms
|
||||||
|
do i=1,k ! iflag will point to the lowest-index 1 in mi
|
||||||
|
if(mi(i).eq.1) then
|
||||||
|
iflag=i
|
||||||
|
exit
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
return
|
||||||
|
end subroutine nextpat101
|
||||||
|
|
||||||
|
subroutine boxit101(reset,e2,ntau,npindex,i1,i2)
|
||||||
|
integer*1 e2(1:ntau)
|
||||||
|
integer indexes(5000,2),fp(0:525000),np(5000)
|
||||||
|
logical reset
|
||||||
|
common/boxes/indexes,fp,np
|
||||||
|
|
||||||
|
if(reset) then
|
||||||
|
patterns=-1
|
||||||
|
fp=-1
|
||||||
|
np=-1
|
||||||
|
sc=-1
|
||||||
|
indexes=-1
|
||||||
|
reset=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
indexes(npindex,1)=i1
|
||||||
|
indexes(npindex,2)=i2
|
||||||
|
ipat=0
|
||||||
|
do i=1,ntau
|
||||||
|
if(e2(i).eq.1) then
|
||||||
|
ipat=ipat+ishft(1,ntau-i)
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ip=fp(ipat) ! see what's currently stored in fp(ipat)
|
||||||
|
if(ip.eq.-1) then
|
||||||
|
fp(ipat)=npindex
|
||||||
|
else
|
||||||
|
do while (np(ip).ne.-1)
|
||||||
|
ip=np(ip)
|
||||||
|
enddo
|
||||||
|
np(ip)=npindex
|
||||||
|
endif
|
||||||
|
return
|
||||||
|
end subroutine boxit101
|
||||||
|
|
||||||
|
subroutine fetchit101(reset,e2,ntau,i1,i2)
|
||||||
|
integer indexes(5000,2),fp(0:525000),np(5000)
|
||||||
|
integer lastpat
|
||||||
|
integer*1 e2(ntau)
|
||||||
|
logical reset
|
||||||
|
common/boxes/indexes,fp,np
|
||||||
|
save lastpat,inext
|
||||||
|
|
||||||
|
if(reset) then
|
||||||
|
lastpat=-1
|
||||||
|
reset=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
ipat=0
|
||||||
|
do i=1,ntau
|
||||||
|
if(e2(i).eq.1) then
|
||||||
|
ipat=ipat+ishft(1,ntau-i)
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
index=fp(ipat)
|
||||||
|
|
||||||
|
if(lastpat.ne.ipat .and. index.gt.0) then ! return first set of indices
|
||||||
|
i1=indexes(index,1)
|
||||||
|
i2=indexes(index,2)
|
||||||
|
inext=np(index)
|
||||||
|
elseif(lastpat.eq.ipat .and. inext.gt.0) then
|
||||||
|
i1=indexes(inext,1)
|
||||||
|
i2=indexes(inext,2)
|
||||||
|
inext=np(inext)
|
||||||
|
else
|
||||||
|
i1=-1
|
||||||
|
i2=-1
|
||||||
|
inext=-1
|
||||||
|
endif
|
||||||
|
lastpat=ipat
|
||||||
|
return
|
||||||
|
end subroutine fetchit101
|
||||||
|
|
403
lib/fst280/osd280_74.f90
Normal file
403
lib/fst280/osd280_74.f90
Normal file
@ -0,0 +1,403 @@
|
|||||||
|
subroutine osd280_74(llr,k,apmask,ndeep,message74,cw,nhardmin,dmin)
|
||||||
|
!
|
||||||
|
! An ordered-statistics decoder for the (280,74) code.
|
||||||
|
! Message payload is 50 bits. Any or all of a 24-bit CRC can be
|
||||||
|
! used for detecting incorrect codewords. The remaining CRC bits are
|
||||||
|
! cascaded with the LDPC code for the purpose of improving the
|
||||||
|
! distance spectrum of the code.
|
||||||
|
!
|
||||||
|
! If p1 (0.le.p1.le.24) is the number of CRC24 bits that are
|
||||||
|
! to be used for bad codeword detection, then the argument k should
|
||||||
|
! be set to 50+p1.
|
||||||
|
!
|
||||||
|
! Valid values for k are in the range [50,74].
|
||||||
|
!
|
||||||
|
character*24 c24
|
||||||
|
integer, parameter:: N=280
|
||||||
|
integer*1 apmask(N),apmaskr(N)
|
||||||
|
integer*1, allocatable, save :: gen(:,:)
|
||||||
|
integer*1, allocatable :: genmrb(:,:),g2(:,:)
|
||||||
|
integer*1, allocatable :: temp(:),m0(:),me(:),mi(:),misub(:),e2sub(:),e2(:),ui(:)
|
||||||
|
integer*1, allocatable :: r2pat(:)
|
||||||
|
integer indices(N),nxor(N)
|
||||||
|
integer*1 cw(N),ce(N),c0(N),hdec(N)
|
||||||
|
integer*1, allocatable :: decoded(:)
|
||||||
|
integer*1 message74(74)
|
||||||
|
integer indx(N)
|
||||||
|
real llr(N),rx(N),absrx(N)
|
||||||
|
|
||||||
|
logical first,reset
|
||||||
|
data first/.true./
|
||||||
|
save first
|
||||||
|
|
||||||
|
allocate( genmrb(k,N), g2(N,k) )
|
||||||
|
allocate( temp(k), m0(k), me(k), mi(k), misub(k), e2sub(N-k), e2(N-k), ui(N-k) )
|
||||||
|
allocate( r2pat(N-k), decoded(k) )
|
||||||
|
|
||||||
|
if( first ) then ! fill the generator matrix
|
||||||
|
!
|
||||||
|
! Create generator matrix for partial CRC cascaded with LDPC code.
|
||||||
|
!
|
||||||
|
! Let p2=74-k and p1+p2=24.
|
||||||
|
!
|
||||||
|
! The last p2 bits of the CRC24 are cascaded with the LDPC code.
|
||||||
|
!
|
||||||
|
! The first p1=k-50 CRC24 bits will be used for error detection.
|
||||||
|
!
|
||||||
|
allocate( gen(k,N) )
|
||||||
|
gen=0
|
||||||
|
do i=1,k
|
||||||
|
message74=0
|
||||||
|
message74(i)=1
|
||||||
|
if(i.le.50) then
|
||||||
|
call get_crc24(message74,74,ncrc24)
|
||||||
|
write(c24,'(b24.24)') ncrc24
|
||||||
|
read(c24,'(24i1)') message74(51:74)
|
||||||
|
message74(51:k)=0
|
||||||
|
endif
|
||||||
|
call encode280_74(message74,cw)
|
||||||
|
gen(i,:)=cw
|
||||||
|
enddo
|
||||||
|
|
||||||
|
first=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
rx=llr
|
||||||
|
apmaskr=apmask
|
||||||
|
|
||||||
|
! Hard decisions on the received word.
|
||||||
|
hdec=0
|
||||||
|
where(rx .ge. 0) hdec=1
|
||||||
|
|
||||||
|
! Use magnitude of received symbols as a measure of reliability.
|
||||||
|
absrx=abs(rx)
|
||||||
|
call indexx(absrx,N,indx)
|
||||||
|
|
||||||
|
! Re-order the columns of the generator matrix in order of decreasing reliability.
|
||||||
|
do i=1,N
|
||||||
|
genmrb(1:k,i)=gen(1:k,indx(N+1-i))
|
||||||
|
indices(i)=indx(N+1-i)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
! Do gaussian elimination to create a generator matrix with the most reliable
|
||||||
|
! received bits in positions 1:k in order of decreasing reliability (more or less).
|
||||||
|
do id=1,k ! diagonal element indices
|
||||||
|
do icol=id,k+20 ! The 20 is ad hoc - beware
|
||||||
|
iflag=0
|
||||||
|
if( genmrb(id,icol) .eq. 1 ) then
|
||||||
|
iflag=1
|
||||||
|
if( icol .ne. id ) then ! reorder column
|
||||||
|
temp(1:k)=genmrb(1:k,id)
|
||||||
|
genmrb(1:k,id)=genmrb(1:k,icol)
|
||||||
|
genmrb(1:k,icol)=temp(1:k)
|
||||||
|
itmp=indices(id)
|
||||||
|
indices(id)=indices(icol)
|
||||||
|
indices(icol)=itmp
|
||||||
|
endif
|
||||||
|
do ii=1,k
|
||||||
|
if( ii .ne. id .and. genmrb(ii,id) .eq. 1 ) then
|
||||||
|
genmrb(ii,1:N)=ieor(genmrb(ii,1:N),genmrb(id,1:N))
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
exit
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
g2=transpose(genmrb)
|
||||||
|
|
||||||
|
! The hard decisions for the k MRB bits define the order 0 message, m0.
|
||||||
|
! Encode m0 using the modified generator matrix to find the "order 0" codeword.
|
||||||
|
! Flip various combinations of bits in m0 and re-encode to generate a list of
|
||||||
|
! codewords. Return the member of the list that has the smallest Euclidean
|
||||||
|
! distance to the received word.
|
||||||
|
|
||||||
|
hdec=hdec(indices) ! hard decisions from received symbols
|
||||||
|
m0=hdec(1:k) ! zero'th order message
|
||||||
|
absrx=absrx(indices)
|
||||||
|
rx=rx(indices)
|
||||||
|
apmaskr=apmaskr(indices)
|
||||||
|
|
||||||
|
call mrbencode74(m0,c0,g2,N,k)
|
||||||
|
nxor=ieor(c0,hdec)
|
||||||
|
nhardmin=sum(nxor)
|
||||||
|
dmin=sum(nxor*absrx)
|
||||||
|
|
||||||
|
cw=c0
|
||||||
|
ntotal=0
|
||||||
|
nrejected=0
|
||||||
|
npre1=0
|
||||||
|
npre2=0
|
||||||
|
|
||||||
|
if(ndeep.eq.0) goto 998 ! norder=0
|
||||||
|
if(ndeep.gt.6) ndeep=6
|
||||||
|
if( ndeep.eq. 1) then
|
||||||
|
nord=1
|
||||||
|
npre1=0
|
||||||
|
npre2=0
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
elseif(ndeep.eq.2) then
|
||||||
|
nord=1
|
||||||
|
npre1=1
|
||||||
|
npre2=0
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
elseif(ndeep.eq.3) then
|
||||||
|
nord=1
|
||||||
|
npre1=1
|
||||||
|
npre2=1
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
ntau=14
|
||||||
|
elseif(ndeep.eq.4) then
|
||||||
|
nord=2
|
||||||
|
npre1=1
|
||||||
|
npre2=1
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
ntau=17
|
||||||
|
elseif(ndeep.eq.5) then
|
||||||
|
nord=3
|
||||||
|
npre1=1
|
||||||
|
npre2=1
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
ntau=19
|
||||||
|
elseif(ndeep.eq.6) then
|
||||||
|
nord=4
|
||||||
|
npre1=1
|
||||||
|
npre2=1
|
||||||
|
nt=40
|
||||||
|
ntheta=12
|
||||||
|
ntau=19
|
||||||
|
endif
|
||||||
|
|
||||||
|
do iorder=1,nord
|
||||||
|
misub(1:k-iorder)=0
|
||||||
|
misub(k-iorder+1:k)=1
|
||||||
|
iflag=k-iorder+1
|
||||||
|
do while(iflag .ge.0)
|
||||||
|
if(iorder.eq.nord .and. npre1.eq.0) then
|
||||||
|
iend=iflag
|
||||||
|
else
|
||||||
|
iend=1
|
||||||
|
endif
|
||||||
|
d1=0.
|
||||||
|
do n1=iflag,iend,-1
|
||||||
|
mi=misub
|
||||||
|
mi(n1)=1
|
||||||
|
if(any(iand(apmaskr(1:k),mi).eq.1)) cycle
|
||||||
|
ntotal=ntotal+1
|
||||||
|
me=ieor(m0,mi)
|
||||||
|
if(n1.eq.iflag) then
|
||||||
|
call mrbencode74(me,ce,g2,N,k)
|
||||||
|
e2sub=ieor(ce(k+1:N),hdec(k+1:N))
|
||||||
|
e2=e2sub
|
||||||
|
nd1kpt=sum(e2sub(1:nt))+1
|
||||||
|
d1=sum(ieor(me(1:k),hdec(1:k))*absrx(1:k))
|
||||||
|
else
|
||||||
|
e2=ieor(e2sub,g2(k+1:N,n1))
|
||||||
|
nd1kpt=sum(e2(1:nt))+2
|
||||||
|
endif
|
||||||
|
if(nd1kpt .le. ntheta) then
|
||||||
|
call mrbencode74(me,ce,g2,N,k)
|
||||||
|
nxor=ieor(ce,hdec)
|
||||||
|
if(n1.eq.iflag) then
|
||||||
|
dd=d1+sum(e2sub*absrx(k+1:N))
|
||||||
|
else
|
||||||
|
dd=d1+ieor(ce(n1),hdec(n1))*absrx(n1)+sum(e2*absrx(k+1:N))
|
||||||
|
endif
|
||||||
|
if( dd .lt. dmin ) then
|
||||||
|
dmin=dd
|
||||||
|
cw=ce
|
||||||
|
nhardmin=sum(nxor)
|
||||||
|
nd1kptbest=nd1kpt
|
||||||
|
endif
|
||||||
|
else
|
||||||
|
nrejected=nrejected+1
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
! Get the next test error pattern, iflag will go negative
|
||||||
|
! when the last pattern with weight iorder has been generated.
|
||||||
|
call nextpat74(misub,k,iorder,iflag)
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
if(npre2.eq.1) then
|
||||||
|
reset=.true.
|
||||||
|
ntotal=0
|
||||||
|
do i1=k,1,-1
|
||||||
|
do i2=i1-1,1,-1
|
||||||
|
ntotal=ntotal+1
|
||||||
|
mi(1:ntau)=ieor(g2(k+1:k+ntau,i1),g2(k+1:k+ntau,i2))
|
||||||
|
call boxit74(reset,mi(1:ntau),ntau,ntotal,i1,i2)
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ncount2=0
|
||||||
|
ntotal2=0
|
||||||
|
reset=.true.
|
||||||
|
! Now run through again and do the second pre-processing rule
|
||||||
|
misub(1:k-nord)=0
|
||||||
|
misub(k-nord+1:k)=1
|
||||||
|
iflag=k-nord+1
|
||||||
|
do while(iflag .ge.0)
|
||||||
|
me=ieor(m0,misub)
|
||||||
|
call mrbencode74(me,ce,g2,N,k)
|
||||||
|
e2sub=ieor(ce(k+1:N),hdec(k+1:N))
|
||||||
|
do i2=0,ntau
|
||||||
|
ntotal2=ntotal2+1
|
||||||
|
ui=0
|
||||||
|
if(i2.gt.0) ui(i2)=1
|
||||||
|
r2pat=ieor(e2sub,ui)
|
||||||
|
778 continue
|
||||||
|
call fetchit74(reset,r2pat(1:ntau),ntau,in1,in2)
|
||||||
|
if(in1.gt.0.and.in2.gt.0) then
|
||||||
|
ncount2=ncount2+1
|
||||||
|
mi=misub
|
||||||
|
mi(in1)=1
|
||||||
|
mi(in2)=1
|
||||||
|
if(sum(mi).lt.nord+npre1+npre2.or.any(iand(apmaskr(1:k),mi).eq.1)) cycle
|
||||||
|
me=ieor(m0,mi)
|
||||||
|
call mrbencode74(me,ce,g2,N,k)
|
||||||
|
nxor=ieor(ce,hdec)
|
||||||
|
dd=sum(nxor*absrx)
|
||||||
|
if( dd .lt. dmin ) then
|
||||||
|
dmin=dd
|
||||||
|
cw=ce
|
||||||
|
nhardmin=sum(nxor)
|
||||||
|
endif
|
||||||
|
goto 778
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
call nextpat74(misub,k,nord,iflag)
|
||||||
|
enddo
|
||||||
|
endif
|
||||||
|
|
||||||
|
998 continue
|
||||||
|
! Re-order the codeword to [message bits][parity bits] format.
|
||||||
|
cw(indices)=cw
|
||||||
|
hdec(indices)=hdec
|
||||||
|
message74=cw(1:74)
|
||||||
|
call get_crc24(message74,74,nbadcrc)
|
||||||
|
if(nbadcrc.ne.0) nhardmin=-nhardmin
|
||||||
|
|
||||||
|
return
|
||||||
|
end subroutine osd280_74
|
||||||
|
|
||||||
|
subroutine mrbencode74(me,codeword,g2,N,K)
|
||||||
|
integer*1 me(K),codeword(N),g2(N,K)
|
||||||
|
! fast encoding for low-weight test patterns
|
||||||
|
codeword=0
|
||||||
|
do i=1,K
|
||||||
|
if( me(i) .eq. 1 ) then
|
||||||
|
codeword=ieor(codeword,g2(1:N,i))
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
return
|
||||||
|
end subroutine mrbencode74
|
||||||
|
|
||||||
|
subroutine nextpat74(mi,k,iorder,iflag)
|
||||||
|
integer*1 mi(k),ms(k)
|
||||||
|
! generate the next test error pattern
|
||||||
|
ind=-1
|
||||||
|
do i=1,k-1
|
||||||
|
if( mi(i).eq.0 .and. mi(i+1).eq.1) ind=i
|
||||||
|
enddo
|
||||||
|
if( ind .lt. 0 ) then ! no more patterns of this order
|
||||||
|
iflag=ind
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
ms=0
|
||||||
|
ms(1:ind-1)=mi(1:ind-1)
|
||||||
|
ms(ind)=1
|
||||||
|
ms(ind+1)=0
|
||||||
|
if( ind+1 .lt. k ) then
|
||||||
|
nz=iorder-sum(ms)
|
||||||
|
ms(k-nz+1:k)=1
|
||||||
|
endif
|
||||||
|
mi=ms
|
||||||
|
do i=1,k ! iflag will point to the lowest-index 1 in mi
|
||||||
|
if(mi(i).eq.1) then
|
||||||
|
iflag=i
|
||||||
|
exit
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
return
|
||||||
|
end subroutine nextpat74
|
||||||
|
|
||||||
|
subroutine boxit74(reset,e2,ntau,npindex,i1,i2)
|
||||||
|
integer*1 e2(1:ntau)
|
||||||
|
integer indexes(5000,2),fp(0:525000),np(5000)
|
||||||
|
logical reset
|
||||||
|
common/boxes/indexes,fp,np
|
||||||
|
|
||||||
|
if(reset) then
|
||||||
|
patterns=-1
|
||||||
|
fp=-1
|
||||||
|
np=-1
|
||||||
|
sc=-1
|
||||||
|
indexes=-1
|
||||||
|
reset=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
indexes(npindex,1)=i1
|
||||||
|
indexes(npindex,2)=i2
|
||||||
|
ipat=0
|
||||||
|
do i=1,ntau
|
||||||
|
if(e2(i).eq.1) then
|
||||||
|
ipat=ipat+ishft(1,ntau-i)
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
|
||||||
|
ip=fp(ipat) ! see what's currently stored in fp(ipat)
|
||||||
|
if(ip.eq.-1) then
|
||||||
|
fp(ipat)=npindex
|
||||||
|
else
|
||||||
|
do while (np(ip).ne.-1)
|
||||||
|
ip=np(ip)
|
||||||
|
enddo
|
||||||
|
np(ip)=npindex
|
||||||
|
endif
|
||||||
|
return
|
||||||
|
end subroutine boxit74
|
||||||
|
|
||||||
|
subroutine fetchit74(reset,e2,ntau,i1,i2)
|
||||||
|
integer indexes(5000,2),fp(0:525000),np(5000)
|
||||||
|
integer lastpat
|
||||||
|
integer*1 e2(ntau)
|
||||||
|
logical reset
|
||||||
|
common/boxes/indexes,fp,np
|
||||||
|
save lastpat,inext
|
||||||
|
|
||||||
|
if(reset) then
|
||||||
|
lastpat=-1
|
||||||
|
reset=.false.
|
||||||
|
endif
|
||||||
|
|
||||||
|
ipat=0
|
||||||
|
do i=1,ntau
|
||||||
|
if(e2(i).eq.1) then
|
||||||
|
ipat=ipat+ishft(1,ntau-i)
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
index=fp(ipat)
|
||||||
|
|
||||||
|
if(lastpat.ne.ipat .and. index.gt.0) then ! return first set of indices
|
||||||
|
i1=indexes(index,1)
|
||||||
|
i2=indexes(index,2)
|
||||||
|
inext=np(index)
|
||||||
|
elseif(lastpat.eq.ipat .and. inext.gt.0) then
|
||||||
|
i1=indexes(inext,1)
|
||||||
|
i2=indexes(inext,2)
|
||||||
|
inext=np(inext)
|
||||||
|
else
|
||||||
|
i1=-1
|
||||||
|
i2=-1
|
||||||
|
inext=-1
|
||||||
|
endif
|
||||||
|
lastpat=ipat
|
||||||
|
return
|
||||||
|
end subroutine fetchit74
|
||||||
|
|
Loading…
Reference in New Issue
Block a user