Fixed depth=4. Removed apmask from bpd and osd.
This commit is contained in:
		
							parent
							
								
									c8476b3308
								
							
						
					
					
						commit
						eeffb13719
					
				@ -1,9 +1,9 @@
 | 
				
			|||||||
subroutine bpdecode174(llr,apmask,maxiterations,decoded,cw,nharderror,iter)
 | 
					subroutine bpdecode174(llr,maxiterations,decoded,cw,nharderror,iter)
 | 
				
			||||||
!
 | 
					!
 | 
				
			||||||
! A log-domain belief propagation decoder for the (174,87) code.
 | 
					! A log-domain belief propagation decoder for the (174,87) code.
 | 
				
			||||||
!
 | 
					!
 | 
				
			||||||
integer, parameter:: N=174, K=87, M=N-K
 | 
					integer, parameter:: N=174, K=87, M=N-K
 | 
				
			||||||
integer*1 codeword(N),cw(N),apmask(N)
 | 
					integer*1 codeword(N),cw(N)
 | 
				
			||||||
integer  colorder(N)
 | 
					integer  colorder(N)
 | 
				
			||||||
integer*1 decoded(K)
 | 
					integer*1 decoded(K)
 | 
				
			||||||
integer Nm(7,M)  ! 5, 6, or 7 bits per check 
 | 
					integer Nm(7,M)  ! 5, 6, or 7 bits per check 
 | 
				
			||||||
@ -323,11 +323,7 @@ do iter=0,maxiterations
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
! Update bit log likelihood ratios (tov=0 in iteration 0).
 | 
					! Update bit log likelihood ratios (tov=0 in iteration 0).
 | 
				
			||||||
  do i=1,N
 | 
					  do i=1,N
 | 
				
			||||||
    if( apmask(i) .ne. 1 ) then
 | 
					 | 
				
			||||||
    zn(i)=llr(i)+sum(tov(1:ncw,i))
 | 
					    zn(i)=llr(i)+sum(tov(1:ncw,i))
 | 
				
			||||||
    else
 | 
					 | 
				
			||||||
      zn(i)=llr(i)
 | 
					 | 
				
			||||||
    endif
 | 
					 | 
				
			||||||
  enddo
 | 
					  enddo
 | 
				
			||||||
 | 
					
 | 
				
			||||||
! Check to see if we have a codeword (check before we do any iteration).
 | 
					! Check to see if we have a codeword (check before we do any iteration).
 | 
				
			||||||
 | 
				
			|||||||
@ -1,10 +1,9 @@
 | 
				
			|||||||
subroutine osd174(llr,apmask,ndeep,decoded,cw,nhardmin,dmin)
 | 
					subroutine osd174(llr,ndeep,decoded,cw,nhardmin,dmin)
 | 
				
			||||||
!
 | 
					!
 | 
				
			||||||
! An ordered-statistics decoder for the (174,87) code.
 | 
					! An ordered-statistics decoder for the (174,87) code.
 | 
				
			||||||
! 
 | 
					! 
 | 
				
			||||||
include "ldpc_174_87_params.f90"
 | 
					include "ldpc_174_87_params.f90"
 | 
				
			||||||
 | 
					
 | 
				
			||||||
integer*1 apmask(N),apmaskr(N)
 | 
					 | 
				
			||||||
integer*1 gen(K,N)
 | 
					integer*1 gen(K,N)
 | 
				
			||||||
integer*1 genmrb(K,N),g2(N,K)
 | 
					integer*1 genmrb(K,N),g2(N,K)
 | 
				
			||||||
integer*1 temp(K),m0(K),me(K),mi(K),misub(K),e2sub(N-K),e2(N-K),ui(N-K)
 | 
					integer*1 temp(K),m0(K),me(K),mi(K),misub(K),e2sub(N-K),e2(N-K),ui(N-K)
 | 
				
			||||||
@ -37,7 +36,6 @@ endif
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
! Re-order received vector to place systematic msg bits at the end.
 | 
					! Re-order received vector to place systematic msg bits at the end.
 | 
				
			||||||
rx=llr(colorder+1) 
 | 
					rx=llr(colorder+1) 
 | 
				
			||||||
apmaskr=apmask(colorder+1)
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
! Hard decisions on the received word.
 | 
					! Hard decisions on the received word.
 | 
				
			||||||
hdec=0            
 | 
					hdec=0            
 | 
				
			||||||
@ -90,7 +88,6 @@ hdec=hdec(indices)   ! hard decisions from received symbols
 | 
				
			|||||||
m0=hdec(1:K)         ! zero'th order message
 | 
					m0=hdec(1:K)         ! zero'th order message
 | 
				
			||||||
absrx=absrx(indices) 
 | 
					absrx=absrx(indices) 
 | 
				
			||||||
rx=rx(indices)       
 | 
					rx=rx(indices)       
 | 
				
			||||||
apmaskr=apmaskr(indices)
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
call mrbencode(m0,c0,g2,N,K)
 | 
					call mrbencode(m0,c0,g2,N,K)
 | 
				
			||||||
nxor=ieor(c0,hdec)
 | 
					nxor=ieor(c0,hdec)
 | 
				
			||||||
@ -151,7 +148,6 @@ do iorder=1,nord
 | 
				
			|||||||
      do n1=iflag,iend,-1
 | 
					      do n1=iflag,iend,-1
 | 
				
			||||||
         mi=misub
 | 
					         mi=misub
 | 
				
			||||||
         mi(n1)=1
 | 
					         mi(n1)=1
 | 
				
			||||||
         if(any(iand(apmaskr(1:K),mi).eq.1)) cycle
 | 
					 | 
				
			||||||
         ntotal=ntotal+1
 | 
					         ntotal=ntotal+1
 | 
				
			||||||
         me=ieor(m0,mi)
 | 
					         me=ieor(m0,mi)
 | 
				
			||||||
         if(n1.eq.iflag) then
 | 
					         if(n1.eq.iflag) then
 | 
				
			||||||
@ -222,7 +218,7 @@ if(npre2.eq.1) then
 | 
				
			|||||||
               mi=misub               
 | 
					               mi=misub               
 | 
				
			||||||
               mi(in1)=1
 | 
					               mi(in1)=1
 | 
				
			||||||
               mi(in2)=1
 | 
					               mi(in2)=1
 | 
				
			||||||
               if(sum(mi).lt.nord+npre1+npre2.or.any(iand(apmaskr(1:K),mi).eq.1)) cycle
 | 
					               if(sum(mi).lt.nord+npre1+npre2) cycle
 | 
				
			||||||
               me=ieor(m0,mi)
 | 
					               me=ieor(m0,mi)
 | 
				
			||||||
               call mrbencode(me,ce,g2,N,K)
 | 
					               call mrbencode(me,ce,g2,N,K)
 | 
				
			||||||
               nxor=ieor(ce,hdec)
 | 
					               nxor=ieor(ce,hdec)
 | 
				
			||||||
 | 
				
			|||||||
@ -22,7 +22,7 @@ subroutine js8dec(dd0,icos,newdat,nQSOProgress,nfqso,nftx,ndepth,lapon,lapcqonly
 | 
				
			|||||||
  real llr(3*ND),llra(3*ND),llr0(3*ND),llr1(3*ND),llrap(3*ND)           !Soft symbols
 | 
					  real llr(3*ND),llra(3*ND),llr0(3*ND),llr1(3*ND),llrap(3*ND)           !Soft symbols
 | 
				
			||||||
  real dd0(NMAX)
 | 
					  real dd0(NMAX)
 | 
				
			||||||
  integer icos
 | 
					  integer icos
 | 
				
			||||||
  integer*1 decoded(KK),decoded0(KK),apmask(3*ND),cw(3*ND)
 | 
					  integer*1 decoded(KK),decoded0(KK),cw(3*ND)
 | 
				
			||||||
  integer*1 msgbits(KK)
 | 
					  integer*1 msgbits(KK)
 | 
				
			||||||
  integer apsym(KK)
 | 
					  integer apsym(KK)
 | 
				
			||||||
  integer mcq(28),mde(28),mrrr(16),m73(16),mrr73(16)
 | 
					  integer mcq(28),mde(28),mrrr(16),m73(16),mrr73(16)
 | 
				
			||||||
@ -359,63 +359,13 @@ subroutine js8dec(dd0,icos,newdat,nQSOProgress,nfqso,nftx,ndepth,lapon,lapcqonly
 | 
				
			|||||||
     if(ipass.eq.3) llr(1:24)=0. 
 | 
					     if(ipass.eq.3) llr(1:24)=0. 
 | 
				
			||||||
     if(ipass.eq.4) llr(1:48)=0. 
 | 
					     if(ipass.eq.4) llr(1:48)=0. 
 | 
				
			||||||
     if(ipass.le.4) then
 | 
					     if(ipass.le.4) then
 | 
				
			||||||
        apmask=0
 | 
					 | 
				
			||||||
        llrap=llr
 | 
					        llrap=llr
 | 
				
			||||||
        iaptype=0
 | 
					        iaptype=0
 | 
				
			||||||
     endif
 | 
					     endif
 | 
				
			||||||
        
 | 
					        
 | 
				
			||||||
     !if(ipass .gt. 4) then
 | 
					 | 
				
			||||||
     !   if(.not.lapcqonly) then
 | 
					 | 
				
			||||||
     !      iaptype=naptypes(nQSOProgress,ipass-4)
 | 
					 | 
				
			||||||
     !   else
 | 
					 | 
				
			||||||
     !      iaptype=1
 | 
					 | 
				
			||||||
     !   endif
 | 
					 | 
				
			||||||
     !   if(iaptype.ge.3 .and. (abs(f1-nfqso).gt.napwid .and. abs(f1-nftx).gt.napwid) ) cycle 
 | 
					 | 
				
			||||||
     !   if(iaptype.eq.1 .or. iaptype.eq.2 ) then ! AP,???,??? 
 | 
					 | 
				
			||||||
     !      apmask=0
 | 
					 | 
				
			||||||
     !      apmask(88:115)=1    ! first 28 bits are AP
 | 
					 | 
				
			||||||
     !      apmask(144)=1       ! not free text
 | 
					 | 
				
			||||||
     !      llrap=llr
 | 
					 | 
				
			||||||
     !      if(iaptype.eq.1) llrap(88:115)=apmag*mcq
 | 
					 | 
				
			||||||
     !      if(iaptype.eq.2) llrap(88:115)=apmag*apsym(1:28)
 | 
					 | 
				
			||||||
     !      llrap(116:117)=llra(116:117)  
 | 
					 | 
				
			||||||
     !      llrap(142:143)=llra(142:143)
 | 
					 | 
				
			||||||
     !      llrap(144)=-apmag
 | 
					 | 
				
			||||||
     !   endif
 | 
					 | 
				
			||||||
     !   if(iaptype.eq.3) then   ! mycall, dxcall, ???
 | 
					 | 
				
			||||||
     !      apmask=0
 | 
					 | 
				
			||||||
     !      apmask(88:115)=1   ! mycall
 | 
					 | 
				
			||||||
     !      apmask(116:143)=1  ! hiscall
 | 
					 | 
				
			||||||
     !      apmask(144)=1      ! not free text
 | 
					 | 
				
			||||||
     !      llrap=llr
 | 
					 | 
				
			||||||
     !      llrap(88:143)=apmag*apsym(1:56)
 | 
					 | 
				
			||||||
     !      llrap(144)=-apmag
 | 
					 | 
				
			||||||
     !   endif
 | 
					 | 
				
			||||||
     !   if(iaptype.eq.4 .or. iaptype.eq.5 .or. iaptype.eq.6) then  
 | 
					 | 
				
			||||||
     !      apmask=0
 | 
					 | 
				
			||||||
     !      apmask(88:115)=1   ! mycall
 | 
					 | 
				
			||||||
     !      apmask(116:143)=1  ! hiscall
 | 
					 | 
				
			||||||
     !      apmask(144:159)=1  ! RRR or 73 or RR73
 | 
					 | 
				
			||||||
     !      llrap=llr
 | 
					 | 
				
			||||||
     !      llrap(88:143)=apmag*apsym(1:56)
 | 
					 | 
				
			||||||
     !      if(iaptype.eq.4) llrap(144:159)=apmag*mrrr 
 | 
					 | 
				
			||||||
     !      if(iaptype.eq.5) llrap(144:159)=apmag*m73 
 | 
					 | 
				
			||||||
     !      if(iaptype.eq.6) llrap(144:159)=apmag*mrr73 
 | 
					 | 
				
			||||||
     !   endif
 | 
					 | 
				
			||||||
     !   if(iaptype.eq.7) then   ! ???, dxcall, ???
 | 
					 | 
				
			||||||
     !      apmask=0
 | 
					 | 
				
			||||||
     !      apmask(116:143)=1  ! hiscall
 | 
					 | 
				
			||||||
     !      apmask(144)=1      ! not free text
 | 
					 | 
				
			||||||
     !      llrap=llr
 | 
					 | 
				
			||||||
     !      llrap(115)=llra(115)
 | 
					 | 
				
			||||||
     !      llrap(116:143)=apmag*apsym(29:56)
 | 
					 | 
				
			||||||
     !      llrap(144)=-apmag
 | 
					 | 
				
			||||||
     !   endif
 | 
					 | 
				
			||||||
     !endif
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
     cw=0
 | 
					     cw=0
 | 
				
			||||||
     call timer('bpd174  ',0)
 | 
					     call timer('bpd174  ',0)
 | 
				
			||||||
     call bpdecode174(llrap,apmask,max_iterations,decoded,cw,nharderrors,  &
 | 
					     call bpdecode174(llrap,max_iterations,decoded,cw,nharderrors,  &
 | 
				
			||||||
          niterations)
 | 
					          niterations)
 | 
				
			||||||
     call timer('bpd174  ',1)
 | 
					     call timer('bpd174  ',1)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -425,7 +375,7 @@ subroutine js8dec(dd0,icos,newdat,nQSOProgress,nfqso,nftx,ndepth,lapon,lapcqonly
 | 
				
			|||||||
     endif
 | 
					     endif
 | 
				
			||||||
 | 
					
 | 
				
			||||||
     dmin=0.0
 | 
					     dmin=0.0
 | 
				
			||||||
     if(ndepth.eq.3 .and. nharderrors.lt.0) then
 | 
					     if(ndepth.ge.3 .and. nharderrors.lt.0) then
 | 
				
			||||||
        ndeep=3
 | 
					        ndeep=3
 | 
				
			||||||
        if(abs(nfqso-f1).le.napwid .or. abs(nftx-f1).le.napwid) then
 | 
					        if(abs(nfqso-f1).le.napwid .or. abs(nftx-f1).le.napwid) then
 | 
				
			||||||
          if((ipass.eq.3 .or. ipass.eq.4) .and. .not.nagain) then
 | 
					          if((ipass.eq.3 .or. ipass.eq.4) .and. .not.nagain) then
 | 
				
			||||||
@ -436,7 +386,7 @@ subroutine js8dec(dd0,icos,newdat,nQSOProgress,nfqso,nftx,ndepth,lapon,lapcqonly
 | 
				
			|||||||
        endif
 | 
					        endif
 | 
				
			||||||
        if(nagain) ndeep=5
 | 
					        if(nagain) ndeep=5
 | 
				
			||||||
        call timer('osd174  ',0)
 | 
					        call timer('osd174  ',0)
 | 
				
			||||||
        call osd174(llrap,apmask,ndeep,decoded,cw,nharderrors,dmin)
 | 
					        call osd174(llrap,ndeep,decoded,cw,nharderrors,dmin)
 | 
				
			||||||
        call timer('osd174  ',1)
 | 
					        call timer('osd174  ',1)
 | 
				
			||||||
     endif
 | 
					     endif
 | 
				
			||||||
     nbadcrc=1
 | 
					     nbadcrc=1
 | 
				
			||||||
 | 
				
			|||||||
@ -69,8 +69,11 @@ contains
 | 
				
			|||||||
    ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
					    ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
				
			||||||
    ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
					    ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
				
			||||||
    ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
					    ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
				
			||||||
 | 
					    ! ndepth=4: subtraction, 4 passes, bp+osd
 | 
				
			||||||
    if(ndepth.eq.1) npass=1
 | 
					    if(ndepth.eq.1) npass=1
 | 
				
			||||||
    if(ndepth.ge.2) npass=3
 | 
					    if(ndepth.eq.2) npass=3
 | 
				
			||||||
 | 
					    if(ndepth.ge.3) npass=4
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    do ipass=1,npass
 | 
					    do ipass=1,npass
 | 
				
			||||||
      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
					      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
				
			||||||
      syncmin=ASYNCMIN
 | 
					      syncmin=ASYNCMIN
 | 
				
			||||||
 | 
				
			|||||||
@ -69,8 +69,11 @@ contains
 | 
				
			|||||||
    ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
					    ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
				
			||||||
    ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
					    ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
				
			||||||
    ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
					    ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
				
			||||||
 | 
					    ! ndepth=4: subtraction, 4 passes, bp+osd
 | 
				
			||||||
    if(ndepth.eq.1) npass=1
 | 
					    if(ndepth.eq.1) npass=1
 | 
				
			||||||
    if(ndepth.ge.2) npass=3
 | 
					    if(ndepth.eq.2) npass=3
 | 
				
			||||||
 | 
					    if(ndepth.ge.3) npass=4
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    do ipass=1,npass
 | 
					    do ipass=1,npass
 | 
				
			||||||
      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
					      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
				
			||||||
      syncmin=ASYNCMIN
 | 
					      syncmin=ASYNCMIN
 | 
				
			||||||
 | 
				
			|||||||
@ -69,8 +69,11 @@ contains
 | 
				
			|||||||
    ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
					    ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
				
			||||||
    ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
					    ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
				
			||||||
    ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
					    ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
				
			||||||
 | 
					    ! ndepth=4: subtraction, 4 passes, bp+osd
 | 
				
			||||||
    if(ndepth.eq.1) npass=1
 | 
					    if(ndepth.eq.1) npass=1
 | 
				
			||||||
    if(ndepth.ge.2) npass=3
 | 
					    if(ndepth.eq.2) npass=3
 | 
				
			||||||
 | 
					    if(ndepth.ge.3) npass=4
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    do ipass=1,npass
 | 
					    do ipass=1,npass
 | 
				
			||||||
      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
					      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
				
			||||||
      syncmin=ASYNCMIN
 | 
					      syncmin=ASYNCMIN
 | 
				
			||||||
 | 
				
			|||||||
@ -69,8 +69,11 @@ contains
 | 
				
			|||||||
    ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
					    ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
				
			||||||
    ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
					    ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
				
			||||||
    ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
					    ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
				
			||||||
 | 
					    ! ndepth=4: subtraction, 4 passes, bp+osd
 | 
				
			||||||
    if(ndepth.eq.1) npass=1
 | 
					    if(ndepth.eq.1) npass=1
 | 
				
			||||||
    if(ndepth.ge.2) npass=3
 | 
					    if(ndepth.eq.2) npass=3
 | 
				
			||||||
 | 
					    if(ndepth.ge.3) npass=4
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    do ipass=1,npass
 | 
					    do ipass=1,npass
 | 
				
			||||||
      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
					      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
				
			||||||
      syncmin=ASYNCMIN
 | 
					      syncmin=ASYNCMIN
 | 
				
			||||||
 | 
				
			|||||||
@ -69,8 +69,11 @@ contains
 | 
				
			|||||||
   ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
					   ! ndepth=1: no subtraction, 1 pass, belief propagation only
 | 
				
			||||||
   ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
					   ! ndepth=2: subtraction, 3 passes, belief propagation only
 | 
				
			||||||
   ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
					   ! ndepth=3: subtraction, 3 passes, bp+osd
 | 
				
			||||||
 | 
					   ! ndepth=4: subtraction, 4 passes, bp+osd
 | 
				
			||||||
    if(ndepth.eq.1) npass=1
 | 
					    if(ndepth.eq.1) npass=1
 | 
				
			||||||
    if(ndepth.ge.2) npass=3
 | 
					    if(ndepth.eq.2) npass=3
 | 
				
			||||||
 | 
					    if(ndepth.ge.3) npass=4
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    do ipass=1,npass
 | 
					    do ipass=1,npass
 | 
				
			||||||
      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
					      newdat=.true.  ! Is this a problem? I hijacked newdat.
 | 
				
			||||||
      syncmin=ASYNCMIN
 | 
					      syncmin=ASYNCMIN
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
		Reference in New Issue
	
	Block a user