ldpc_decoder_syndrome_entropy.f90 Source File


Source Code

! SPDX-License-Identifier: GPL-3.0-or-later
! Copyright (C) 2025  Marco Origlia

!    This program is free software: you can redistribute it and/or modify
!    it under the terms of the GNU General Public License as published by
!    the Free Software Foundation, either version 3 of the License, or
!    (at your option) any later version.

!    This program is distributed in the hope that it will be useful,
!    but WITHOUT ANY WARRANTY; without even the implied warranty of
!    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
!    GNU General Public License for more details.

!    You should have received a copy of the GNU General Public License
!    along with this program.  If not, see <https://www.gnu.org/licenses/>.
submodule (ldpc_decoder) ldpc_decoder_syndrome_entropy
  !! author: Marco Origlia
  !! license: GPL-3.0-or-later
  !!
  !! This submodule provides a function that estimates
  !! the entropy of the syndrome based on the a priori
  !! probabilities of the codeword bits.
contains
  real(wp) module function estimate_syndrome_entropy(this, lapri) result(H)
    !! Estimate the entropy of the syndrome given the log-a priori
    !! probability ratios of the bits of the codeword.
    !! The result is an estimate because it neglects possible correlations,
    !! i.e., bits are treated as independent.
    class(TDecoder)      :: this
    !! The decoder
    real(wp), intent(in) :: lapri(this%vnum)
    !! A priori probabilities of the bits

    integer  :: i,j
    real(wp) :: lapri_current_s, exp_lcs

    H = 0

    do i = 1, this%cnum
       ! for each syndrome node, compute the a priori probability
       lapri_current_s = 1e300_wp
       do j = 1, this%c_to_v(i)%N
          lapri_current_s = f_plus_box(lapri_current_s, lapri(this%c_to_v(i)%data(j)))
       end do
       exp_lcs = exp(lapri_current_s)
       H = H + log(1+exp_lcs) &
            - lapri_current_s * exp_lcs / (1 + exp_lcs)
    end do
    H = H / log(2d0)
  end function estimate_syndrome_entropy
end submodule ldpc_decoder_syndrome_entropy