OpenCores
URL https://opencores.org/ocsvn/yahamm/yahamm/trunk

Subversion Repositories yahamm

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /yahamm
    from Rev 1 to Rev 2
    Reverse comparison

Rev 1 → Rev 2

/trunk/yahamm_dec.vhd
0,0 → 1,284
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
 
library yahamm;
use yahamm.matrix_pkg.all;
use yahamm.yahamm_pkg.all;
 
library std;
use std.textio.all;
 
library ieee_proposed;
use ieee_proposed.std_logic_1164_additions.all;
use ieee_proposed.numeric_std_additions.all;
use ieee_proposed.standard_additions.all;
 
-- There are two monitor counters:
--
-- cnt_errors_corrected: number of error correction performed.
-- cnt_errors_detected: numbers of errors detected but not corrected.
--
-- The two never count together and they don't overflow. If CORRECT
-- is false, no correction is performed cnt_errors_corrected never counts.
-- If CORRECT is true and EXTRA_PARITY_BIT is true, cnt_errors_detected
-- never counts because all errors (supposedly single-bit errors) are
-- corrected.
--
-- ERROR_LEN: width of the cnt_errors_corrected and cnt_errors_detected counters.
--
-- dout_valid: dout data valid, it's the en input pipelined. It takes into
-- account the total latency.
--
entity yahamm_dec is
generic (
MESSAGE_LENGTH : natural := 5;
CORRECT : boolean := true;
EXTRA_PARITY_BIT : natural range 0 to 1 := 1;
ONE_PARITY_BIT : boolean := false;
ERROR_LEN : natural := 16
);
port(
clk, rst : in std_logic;
cnt_clr : in std_logic := '0'; -- Clear monitor counters.
en : in std_logic := '1'; -- Input enable.
din : in std_logic_vector(MESSAGE_LENGTH - 1 downto 0); -- Input data.
parity : in std_logic_vector(calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT) + EXTRA_PARITY_BIT - 1 downto 0); -- Parity bits.
dout : out std_logic_vector(MESSAGE_LENGTH - 1 downto 0); -- Out data.
dout_valid : out std_logic; -- dout valid.
cnt_errors_corrected, cnt_errors_detected : out std_logic_vector(ERROR_LEN - 1 downto 0);
log_wrong_bit_pos_data : out std_logic_vector(MESSAGE_LENGTH - 1 downto 0);
log_wrong_bit_pos_parity : out std_logic_vector(calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT) + EXTRA_PARITY_BIT - 1 downto 0)
);
 
end yahamm_dec;
 
architecture std of yahamm_dec is
 
constant NPARITY_BITS : natural := calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT);
constant BLOCK_LENGTH : natural := calc_block_length(MESSAGE_LENGTH, ONE_PARITY_BIT);
constant H : matrix_t(0 to NPARITY_BITS + EXTRA_PARITY_BIT - 1,
0 to BLOCK_LENGTH + EXTRA_PARITY_BIT - 1) :=
get_parity_check_matrix(MESSAGE_LENGTH, EXTRA_PARITY_BIT, ONE_PARITY_BIT);
 
signal din_padded : bit_vector(BLOCK_LENGTH - NPARITY_BITS - 1 downto 0);
signal code_sys, code_nonsys, code_nonsys_q : bit_vector(BLOCK_LENGTH + EXTRA_PARITY_BIT - 1 downto 0);
signal syndrome : bit_vector(NPARITY_BITS + EXTRA_PARITY_BIT - 1 downto 0);
signal wrong_bit : integer range 0 to code_sys'length;
constant SWAPM : matrix_t(0 to BLOCK_LENGTH + EXTRA_PARITY_BIT - 1,
0 to BLOCK_LENGTH + EXTRA_PARITY_BIT - 1) :=
get_form_swap_matrix(MESSAGE_LENGTH, EXTRA_PARITY_BIT, ONE_PARITY_BIT);
 
signal correction_en : boolean;
signal cnt_errors_corrected_int, cnt_errors_detected_int : unsigned(ERROR_LEN - 1 downto 0);
signal log_wrong_bit_pos_data_sys, log_wrong_bit_pos_data_nonsys : bit_vector(BLOCK_LENGTH + EXTRA_PARITY_BIT - 1 downto 0);
 
signal dout_valid_p0 : std_logic;
begin
 
check_parameters(BLOCK_LENGTH, NPARITY_BITS, MESSAGE_LENGTH, EXTRA_PARITY_BIT, ONE_PARITY_BIT, CORRECT);
 
cnt_errors_corrected <= std_logic_vector(cnt_errors_corrected_int);
cnt_errors_detected <= std_logic_vector(cnt_errors_detected_int);
-- Pad din with zeros on the left, so that din_padded'length = BLOCK_LENGTH.
-- This allow the user to reduce din width.
din_padded(MESSAGE_LENGTH - 1 downto 0) <= to_bitvector(din);
gen_din_padding: if BLOCK_LENGTH - NPARITY_BITS > MESSAGE_LENGTH generate
din_padded(BLOCK_LENGTH - NPARITY_BITS - 1 downto MESSAGE_LENGTH) <= (others => '0');
end generate gen_din_padding;
 
-- Wire data and parity inputs in the systematic code code_sys (data
-- on LSB, parity on MSB).
code_sys <= to_bitvector(parity) & din_padded;
-- Get the non-systematic code code_nonsys by swapping the
-- systematic code code_sys. The non-systematic code is needed to
-- obtain an immediately meaningful syndrome. This is timing-safe:
-- no logic here, it's purely wiring.
code_nonsys <= xor_multiply_vec(SWAPM, code_sys);
 
-- Output log_wrong_bit_pos_log, uses log_wrong_bit_pos_log_nonsys is padded
-- as din_padded
log_wrong_bit_pos_data_sys <= xor_multiply_vec(SWAPM, log_wrong_bit_pos_data_nonsys);
log_wrong_bit_pos_data <= To_StdLogicVector(log_wrong_bit_pos_data_sys(MESSAGE_LENGTH-1 downto 0));
log_wrong_bit_pos_parity <= To_StdLogicVector(log_wrong_bit_pos_data_sys(BLOCK_LENGTH + EXTRA_PARITY_BIT - 1 downto BLOCK_LENGTH - NPARITY_BITS));
-- purpose: Compute error syndrome from the non-systematic code
-- (input) and the non-systemacic parity check matrix H. Also delay
-- code_nonsys to have code_nonsys_q synchronous with syndrome. And start
-- pipelining en input.
-- type : sequential
-- inputs : clk, rst, code_nonsys
-- outputs: syndrome
syndrome_proc: process (clk, rst) is
begin -- process syndrome_proc
if rst = '1' then -- asynchronous reset (active high)
syndrome <= (others => '0');
code_nonsys_q <= (others => '0');
dout_valid_p0 <= '0';
elsif rising_edge(clk) then -- rising clock edge
syndrome <= xor_multiply_vec(H, code_nonsys);
code_nonsys_q <= code_nonsys;
dout_valid_p0 <= en;
end if;
end process syndrome_proc;
 
-- purpose: Enable error correction (signal correction_en) for a single bit
-- error. Dependent from the generic parameters. If correction is enabled
-- wrong_bit signal is assigned the position of the wrong bit.
-- type : combinational
-- inputs : syndrome
-- outputs: correction_enabled
correction_enable_proc: process (syndrome) is
begin -- process correction_enable_proc
wrong_bit <= 0;
case CORRECT is
when false =>
-- Entity does not implement correction.
correction_en <= false;
when true =>
-- Entity implements correction.
 
case EXTRA_PARITY_BIT is
when 0 =>
-- SEC case (see table). Always correct.
correction_en <= true;
 
-- The wrong bit is the syndrome itself.
wrong_bit <= to_integer(unsigned(To_StdULogicVector(syndrome)));
when 1 =>
-- SECDED case (see table). The error, if any, is a single error to be
-- corrected if the extra parity bit in the syndrome is '1'.
if syndrome(syndrome'high) = '0' then
-- Double error: don't correct.
correction_en <= false;
else
-- Single error: correct.
correction_en <= true;
 
-- The wrong bit is not just the syndrome, because the
-- syndrome has the extra parity bit as MSB bit.
if or_reduce(syndrome(syndrome'high-1 downto 0)) = '0' then
-- No other error. So the extra parity bit itself is
-- wrong, that in this implementation is the MSB of
-- the non-systematic code word.
wrong_bit <= code_nonsys_q'length;
else
-- Extra parity bit '1', ignore it for wrong_bit position.
wrong_bit <= to_integer(unsigned(To_StdULogicVector(syndrome(NPARITY_BITS-1 downto 0))));
end if;
end if;
end case;
end case;
 
end process correction_enable_proc;
 
-- purpose: Decode the non systematic code code_nonsys_q and drive
-- output dout. Single error correction is performed, depending on
-- the configuration.
-- type : sequential
-- inputs : clk, rst, code_nonsys_q, syndrome
-- outputs: dout
decode_proc: process (clk, rst) is
variable iserror : boolean; -- parity error condition
variable code_sys_dec, code_nonsys_dec : bit_vector(code_sys'range);
begin -- process decode_proc
if rst = '1' then -- asynchronous reset (active high)
dout <= (others => '0');
dout_valid <= '0';
elsif rising_edge(clk) then -- rising clock edge
 
if dout_valid_p0 = '0' then
dout <= (others => '0');
dout_valid <= '0';
else
code_nonsys_dec := code_nonsys_q;
iserror := or_reduce(syndrome) = '1';
if correction_en and iserror then
code_nonsys_dec(wrong_bit-1) := not code_nonsys_q(wrong_bit-1);
end if;
code_sys_dec := xor_multiply_vec(SWAPM, code_nonsys_dec);
dout <= To_StdLogicVector(code_sys_dec(MESSAGE_LENGTH - 1 downto 0));
dout_valid <= '1';
end if;
end if;
end process decode_proc;
 
-- purpose: Monitor counters.
-- type : sequential
-- inputs : clk, rst, syndrome, correction_en
-- outputs: cnt_errors_corrected_int, cnt_errors_detected_int, log_wrong_bit_pos_log
cnt_proc: process (clk, rst) is
variable iserror : boolean; -- parity error condition
begin -- process cnt_proc
if rst = '1' then -- asynchronous reset (active high)
cnt_errors_detected_int <= (others => '0');
cnt_errors_corrected_int <= (others => '0');
elsif rising_edge(clk) then -- rising clock edge
if cnt_clr = '1' then
-- synchronous clear
cnt_errors_detected_int <= (others => '0');
cnt_errors_corrected_int <= (others => '0');
else
iserror := or_reduce(syndrome) = '1';
if iserror then
if correction_en then
if and_reduce(cnt_errors_corrected_int) /= '1' then
cnt_errors_corrected_int <= cnt_errors_corrected_int + 1;
end if;
else
if and_reduce(cnt_errors_detected_int) /= '1' then
cnt_errors_detected_int <= cnt_errors_detected_int + 1;
end if;
end if;
end if;
end if;
end if;
end process cnt_proc;
 
-- purpose: Monitor counters.
-- type : sequential
-- inputs : clk, rst, syndrome, correction_en
-- outputs: cnt_errors_corrected_int, cnt_errors_detected_int, log_wrong_bit_pos_log
log_wrong_bit_gen: if CORRECT generate
log_wrong_bit_proc: process (clk, rst) is
variable iserror : boolean; -- parity error condition
begin -- process cnt_proc
if rst = '1' then
log_wrong_bit_pos_data_nonsys <= (others => '0');
elsif rising_edge(clk) then
if cnt_clr = '1' then
log_wrong_bit_pos_data_nonsys <= (others => '0');
else
iserror := or_reduce(syndrome) = '1';
if iserror then
if correction_en then
 
-- Note: wrong_bit refers to the wrong bit of the code in
-- non-systematic form. Indeed this is swapped to
-- systematic form for the output.
log_wrong_bit_pos_data_nonsys(wrong_bit-1) <= '1';
 
end if;
end if;
end if;
end if;
end process log_wrong_bit_proc;
end generate log_wrong_bit_gen;
end architecture std;
/trunk/yahamm_enc.vhd
0,0 → 1,103
-- CORRECT: set to true to correct errors at the cost of decreasing error
-- detection (see table).
--
-- SEC = single bit error corrected
-- SED = single bit error detected
-- DED = double bit error detected
-- TED = triple bit error detected
--
-- EXTRA_PARITY_BIT | CORRECT FALSE TRUE
-------------------------------------------------------------------------------
-- FALSE | SED-DED SEC
-- -----------------------------------------------------------
-- TRUE | SED-DED-TED SEC-DED
-------------------------------------------------------------------------------
--
-- Note that, for example, SEC-DED (EXTRA_PARITY_BIT = true, CORRECT =
-- true) means that triple bit errors are not detected and messages
-- will be wrongly corrected because the correction corrects toward
-- the code word within the smaller hamming distance. Practically you
-- usually know that something is very wrong with your communication
-- channel because you will also see double bit errors. Then you
-- should not trust corrected data at all.
 
library ieee;
use ieee.std_logic_1164.all;
 
library ieee_proposed;
use ieee_proposed.standard_additions.all;
use ieee_proposed.std_logic_1164_additions.all;
 
library yahamm;
use yahamm.matrix_pkg.all;
use yahamm.hamming_pkg.all;
 
entity yahamm_enc is
generic (
MESSAGE_LENGTH : natural := 5;
EXTRA_PARITY_BIT : natural range 0 to 1 := 1;
ONE_PARITY_BIT : boolean := false
);
port(
clk, rst : in std_logic;
en : in std_logic := '1'; -- Synchronous output enable .
din : in std_logic_vector(MESSAGE_LENGTH - 1 downto 0); -- Input data.
dout : out std_logic_vector(MESSAGE_LENGTH - 1 downto 0); -- Out data.
dout_valid : out std_logic;
parity : out std_logic_vector(calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT) + EXTRA_PARITY_BIT - 1 downto 0) -- Parity bits.
);
 
end yahamm_enc;
 
architecture std of yahamm_enc is
 
constant NPARITY_BITS : natural := calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT);
constant BLOCK_LENGTH : natural := calc_block_length(MESSAGE_LENGTH, ONE_PARITY_BIT);
constant G : matrix_t(0 to BLOCK_LENGTH + EXTRA_PARITY_BIT - 1,
0 to BLOCK_LENGTH - NPARITY_BITS - 1) :=
get_code_generator_matrix(MESSAGE_LENGTH, EXTRA_PARITY_BIT, ONE_PARITY_BIT);
 
signal din_padded : bit_vector(BLOCK_LENGTH - NPARITY_BITS - 1 downto 0);
signal code_sys : std_ulogic_vector(G'reverse_range(1)); -- systematic code
begin
 
check_parameters(BLOCK_LENGTH, NPARITY_BITS, MESSAGE_LENGTH, EXTRA_PARITY_BIT, ONE_PARITY_BIT);
 
din_padded(MESSAGE_LENGTH - 1 downto 0) <= to_bitvector(din);
pad_gen: if MESSAGE_LENGTH < BLOCK_LENGTH - NPARITY_BITS generate
-- Pad din with zeros on the left, so that din_padded'length = BLOCK_LENGTH.
-- This allow the user to reduce din width.
din_padded(BLOCK_LENGTH - NPARITY_BITS - 1 downto MESSAGE_LENGTH) <= (others => '0');
end generate pad_gen;
-- Wire systematic code signal code_sys on dout and parity output ports.
-- Because of the form of the code generator matrix G, data are the LSB part
-- of code and parity the MSB part.
parity <= to_slv(code_sys(code_sys'high downto code_sys'high - (EXTRA_PARITY_BIT + NPARITY_BITS) + 1));
dout <= to_slv(code_sys(MESSAGE_LENGTH - 1 downto 0));
-- purpose: Sequentially encode input with output enable.
-- type : sequential
-- inputs : clk, rst, d_sig
-- outputs: msg_sys
encode_proc: process (clk, rst) is
begin -- process encode_proc
if rst = '1' then -- asynchronous reset (active high)
code_sys <= (others => '0');
dout_valid <= '0';
elsif rising_edge(clk) then -- rising clock edge
 
if en = '0' then -- syncronous output enable
code_sys <= (others => '0');
dout_valid <= '0';
else
code_sys <= To_StdULogicVector(xor_multiply_vec(G, din_padded));
dout_valid <= '1';
end if;
end if;
end process encode_proc;
 
end architecture std;
/trunk/yahamm_pkg.vhd
0,0 → 1,466
library ieee;
use ieee.std_logic_1164.all;
use ieee.math_real.all;
use ieee.numeric_std.all;
 
library ieee_proposed;
use ieee_proposed.standard_additions.all;
use ieee_proposed.std_logic_1164_additions.all;
 
library yahamm;
use yahamm.matrix_pkg.all;
 
package yahamm_pkg is
 
component yahamm_dec is
generic (
MESSAGE_LENGTH : natural;
CORRECT : boolean;
EXTRA_PARITY_BIT : natural range 0 to 1;
ONE_PARITY_BIT : boolean;
ERROR_LEN : natural;
NPARITY_BITS : natural;
BLOCK_LENGTH : natural);
port (
clk, rst : in std_logic;
en : in std_logic;
din : in std_logic_vector(MESSAGE_LENGTH - 1 downto 0);
parity : in std_logic_vector(NPARITY_BITS + EXTRA_PARITY_BIT - 1 downto 0);
dout : out std_logic_vector(MESSAGE_LENGTH - 1 downto 0);
cnt_errors_corrected, cnt_errors_detected : out std_logic_vector(ERROR_LEN - 1 downto 0));
end component yahamm_dec;
 
component yahamm_enc is
generic (
MESSAGE_LENGTH : natural;
EXTRA_PARITY_BIT : natural range 0 to 1;
ONE_PARITY_BIT : boolean;
NPARITY_BITS : natural;
BLOCK_LENGTH : natural);
port (
clk, rst : in std_logic;
en : in std_logic := '1';
din : in std_logic_vector(MESSAGE_LENGTH - 1 downto 0);
dout : out std_logic_vector(MESSAGE_LENGTH - 1 downto 0);
parity : out std_logic_vector(NPARITY_BITS + EXTRA_PARITY_BIT - 1 downto 0));
end component yahamm_enc;
function get_parity_check_matrix (
MESSAGE_LENGTH : natural;
EXTRA_PARITY : natural range 0 to 1 := 1;
ONE_PARITY_BIT : boolean := false)
return matrix_t;
 
function get_code_generator_matrix (
MESSAGE_LENGTH : natural;
EXTRA_PARITY : in natural range 0 to 1 := 1; -- number of data (non parity) bits
ONE_PARITY_BIT : boolean := false)
return matrix_t;
 
function calc_nparity_bits (
k : in natural;
ONE_PARITY_BIT : boolean := false)
return natural;
function calc_block_length (
k : in natural;
ONE_PARITY_BIT : boolean := false)
return natural;
 
procedure check_parameters (
constant BLOCK_LENGTH : in natural;
constant NPARITY_BITS : in natural;
constant MESSAGE_LENGTH : in natural;
constant EXTRA_PARITY_BIT : in natural;
constant ONE_PARITY_BIT : in boolean;
constant CORRECT : in boolean := false
);
function xor_multiply (
A : matrix_t;
B : in matrix_t)
return matrix_t;
function xor_multiply_vec (
A : matrix_t;
x : in bit_vector)
return bit_vector;
 
function get_form_swap_matrix (
MESSAGE_LENGTH : natural;
EXTRA_PARITY : natural;
ONE_PARITY_BIT : boolean := false)
return matrix_t;
end package yahamm_pkg;
 
package body yahamm_pkg is
 
-- purpose: Return a matrix S that can be used to tranform a parity
-- check matrix or a code generator matrix M from non-systematic
-- form to systematic form MS and viceversa (because S = S
-- transposed = S^-1). Use as as MS = M x S.
-- Also works for M with extra parity bit: set EXTRA_PARITY to 1 and
-- the swap matrix increases of one extra column and one extra row
-- (as the parity check matrix) and the extra column is not swapped.
function get_form_swap_matrix (
MESSAGE_LENGTH : natural;
EXTRA_PARITY : in natural;
ONE_PARITY_BIT : boolean := false)
return matrix_t is
constant BLOCK_LENGTH : natural := calc_block_length(MESSAGE_LENGTH, ONE_PARITY_BIT);
constant NPARITY_BITS : natural := calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT);
variable idmatrix : matrix_t(0 to BLOCK_LENGTH + EXTRA_PARITY - 1, 0 to BLOCK_LENGTH + EXTRA_PARITY - 1) := (others => (others => '0'));
variable swap_matrix : matrix_t(0 to BLOCK_LENGTH + EXTRA_PARITY - 1, 0 to BLOCK_LENGTH + EXTRA_PARITY - 1); -- output
begin -- function get_systematic_swap_matrix
 
-- Fill up the identity matrix idmatrix. It's initialized to zeros, so
-- just write ones on the diagonal.
for irow in idmatrix'range(1) loop
for icol in idmatrix'range(2) loop
if irow = icol then
idmatrix(irow, icol) := '1';
end if;
end loop;
end loop;
 
-- Swap columns corresponding to parity bits position in the
-- parity check matrix (0, 1, 3, 7 etc...) with the right-most
-- columns (starting with inner possibile rightmost). E.g. let's
-- say that, with the given message length, BLOCK_LENGTH is 7 and
-- the parity bits are in positions 0, 1 and 3. The swap will be:
-- 0 <-> 5
-- 1 <-> 6
-- 3 <-> 7
--
-- Note: if EXTRA_PARITY is set, last colum is ignored because is not to be
-- swapped.
swap_matrix := idmatrix;
for np in 0 to NPARITY_BITS-1 loop
swap_cols(swap_matrix, 2**np - 1, BLOCK_LENGTH - NPARITY_BITS + np);
end loop; -- np
 
return swap_matrix;
end function get_form_swap_matrix;
-- purpose: Return the result of the matrix M x vector v product. Internal sums are
-- replaced by xor operations. E.g.:
-- [1 1; 0 1] * [a; b] = [a xor b; b]
-- [1 1; 0 1] * [1 1; 1 0] = [0 1; 1 0]
function xor_multiply (
A : matrix_t;
B : matrix_t)
return matrix_t is
 
--variable y : bit_vector(A'reverse_range(1));
variable y : matrix_t(A'range(1), B'range(2));
variable element : bit;
begin -- function matrix_multiply
--report "xor_multiply: Matrix A sized "
-- & integer'image(A'length(1)) & "x" & integer'image(A'length(2))
-- & ". Matrix B sized "
-- & integer'image(B'length(1)) & "x" & integer'image(B'length(2)) & "."
-- severity note;
 
assert A'length(2) = B'length(1)
report "Cannot multiply matrix A sized "
& integer'image(A'length(1)) & "x" & integer'image(A'length(2))
& " with matrix B sized "
& integer'image(B'length(1)) & "x" & integer'image(B'length(2)) & "."
severity error;
for Arow in A'range(1) loop
for Bcol in B'range(2) loop
element := '0';
for Acol in A'range(2) loop
element := element xor (A(Arow, Acol) and B(Acol, Bcol));
end loop; -- i
y(Arow, Bcol) := element;
--report
-- "(" & integer'image(Arow) & ", " & integer'image(Bcol) & "): " &
-- "y(Arow, Bcol) := " & bit'image(element)
-- severity note;
end loop; -- Bcol
 
--assert false report "y(" & integer'image(y'length-Arow-1) & ") := " & bit'image(y(y'length-Arow-1)) severity note;
end loop;
 
--pretty_print_matrix(A);
--pretty_print_matrix(B);
--pretty_print_matrix(y);
return y;
end function xor_multiply;
 
 
-- purpose: Return the result of the matrix operation y = A*x using
-- xor_multiply function. See xor_multiply comment for details.
function xor_multiply_vec (
A : matrix_t;
x : bit_vector)
return bit_vector is
 
variable B : matrix_t(x'range, 0 to 0);
variable C : matrix_t(A'range(1), 0 to 0);
variable y : bit_vector(A'reverse_range(1)); -- output
begin -- function matrix_multiply
 
assert A'length(2) = x'length
report "Cannot multiply matrix A sized "
& integer'image(A'length(1)) & "x" & integer'image(A'length(2))
& " with vector x of length "
& integer'image(x'length) & "."
severity error;
-- Transform bit_vector x into a 1-column matrix_t.
for i in x'range loop
B(i, 0) := x(i);
end loop; -- i
C := xor_multiply(A, B);
 
-- Transform the 1-column matrix_t C into a bit_vector.
for i in C'range(1) loop
y(i) := C(i, 0);
end loop; -- i
 
--report "xor_multiply_vec: Matrix A sized "
-- & integer'image(A'length(1)) & "x" & integer'image(A'length(2))
-- & ". Matrix B sized "
-- & integer'image(B'length(1)) & "x" & integer'image(B'length(2)) & "."
-- severity note;
 
--pretty_print_matrix(A);
--pretty_print_matrix(B);
--pretty_print_matrix(C);
--pretty_print_vector(y);
return y;
end function xor_multiply_vec;
-- purpose: Generate the parity check matrix for a given message length. The
-- matrix is in non-systematic form.
function get_parity_check_matrix (
MESSAGE_LENGTH : natural;
EXTRA_PARITY : natural range 0 to 1 := 1; -- increase hamming distance to 4
ONE_PARITY_BIT : boolean := false)
return matrix_t is
 
constant NPARITY_BITS : natural := calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT);
constant BLOCK_LENGTH : natural := calc_block_length(MESSAGE_LENGTH, ONE_PARITY_BIT);
 
variable m : matrix_t(0 to NPARITY_BITS-1, 0 to BLOCK_LENGTH-1);
variable parity, bit_pos : natural;
variable ubit_pos : unsigned(BLOCK_LENGTH - 1 downto 0);
 
-- add 1 row and 1 column respect to m to build a parity check
-- matrix with extra parity bit.
variable m_extra : matrix_t(0 to m'length(1), 0 to m'length(2));
variable hecol : bit_vector(m_extra'range(1));
 
begin -- function get_parity_check_matrix
 
if ONE_PARITY_BIT then
m := (0 => (others => '1'));
return m;
end if;
 
for iparity in m'range(1) loop
parity := 2**iparity;
 
if parity >= 2 then
for bit_pos in 0 to parity-2 loop
m(iparity, bit_pos) := '0';
end loop;
end if;
for bit_pos in parity-1 to m'length(2)-1 loop
ubit_pos := to_unsigned(bit_pos+1, BLOCK_LENGTH);
m(iparity, bit_pos) := to_bit(ubit_pos(iparity));
 
end loop; -- bit_pos
end loop; -- iparity
 
if EXTRA_PARITY = 0 then
return m;
else
-- m_extra is the parity check matrix with extra parity bits.
-- It is constructed from m in 2 steps. m_extra has an extra
-- row and extra column respect to m.
 
-- 1. copy m in m_extra.
for irow in m'range(1) loop
for icol in m'range(2) loop
m_extra(irow, icol) := m(irow, icol);
end loop;
end loop;
-- 2. Add extra row with '1'.
for icol in m_extra'range(2) loop
m_extra(m_extra'high(1), icol) := '1';
end loop;
 
return m_extra;
end if;
end function get_parity_check_matrix;
 
-- purpose: Create the code generator matrix in systematic form.
function get_code_generator_matrix (
MESSAGE_LENGTH : natural;
EXTRA_PARITY : natural range 0 to 1 := 1; -- increase hamming ndistance to 4
ONE_PARITY_BIT : boolean := false)
 
return matrix_t is
 
constant BLOCK_LENGTH : natural := calc_block_length(MESSAGE_LENGTH, ONE_PARITY_BIT);
constant NPARITY_BITS : natural := calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT);
 
-- The only reason the code generator matrix is systematic is because H
-- returned from get_code_generator_matrix is systematic (see
-- make_systematic in code_generator_matrix).
variable H : matrix_t(0 to NPARITY_BITS + EXTRA_PARITY - 1,
0 to BLOCK_LENGTH + EXTRA_PARITY - 1) := get_parity_check_matrix(MESSAGE_LENGTH,
EXTRA_PARITY,
ONE_PARITY_BIT);
 
-- G is the code generator matrix.
variable G : matrix_t(0 to BLOCK_LENGTH - NPARITY_BITS - 1, 0 to BLOCK_LENGTH + EXTRA_PARITY - 1);
-- GT is G transposed.
variable GT : matrix_t(G'range(2), G'range(1));
variable gcol : bit_vector(H'range(2)); -- G matrix column
variable hcol : bit_vector(H'range(1)); -- H matrix column
 
variable swap_matrix : matrix_t(0 to BLOCK_LENGTH + EXTRA_PARITY - 1, 0 to BLOCK_LENGTH + EXTRA_PARITY - 1);
begin -- function get_code_generator_matrix
-- Identity submatrix on the left (I_k)
for col in 0 to BLOCK_LENGTH - NPARITY_BITS - 1 loop
gcol := (others => '0');
gcol(col) := '1';
set_col(G, col, gcol);
end loop; -- col
 
-- transform H in systematic form
swap_matrix := get_form_swap_matrix(MESSAGE_LENGTH, EXTRA_PARITY, ONE_PARITY_BIT);
H := xor_multiply(H, swap_matrix);
 
if EXTRA_PARITY = 1 then
-- This is a trick that avoids a very tedious row reduction.
for icol in H'range(2) loop
hcol := get_col(H, icol);
if xor_reduce(to_slv(hcol)) = '0' then
H(H'high(1), icol) := '0';
end if;
end loop; -- icol
end if;
 
--pretty_print_matrix(H);
--pretty_print_matrix(xor_multiply(H, swap_matrix));
-- Submatrix A transposed.
for col in BLOCK_LENGTH - NPARITY_BITS to BLOCK_LENGTH + EXTRA_PARITY - 1 loop
for row in 0 to BLOCK_LENGTH - NPARITY_BITS - 1 loop
G(row, col) := H(col-(BLOCK_LENGTH-NPARITY_BITS), row);
end loop;
end loop;
-- transpose G
for irow in G'range(1) loop
for icol in G'range(2) loop
GT(icol, irow) := G(irow, icol);
end loop;
end loop;
 
return GT;
end function get_code_generator_matrix;
 
-- purpose: Calculate the number of parity bits (r) needed for the
-- specified message length (k). The code has m = 2^r - r - 1 for r >= 2.
function calc_nparity_bits (
k : natural;
ONE_PARITY_BIT : boolean := false)
return natural is
variable r : natural := 0;
begin -- function calc_nparity_bits
 
-- assert k > 0 report "Code construction not implement for message length 0." severity failure;
 
if ONE_PARITY_BIT then
return 1;
end if;
r := 0;
while true loop
if 2**r - r - 1 >= k then
return r;
end if;
 
r := r + 1;
end loop;
 
report "This should never happen." severity failure;
return 0;
end function calc_nparity_bits;
-- purpose: Calculate the code block length n for the specified
-- message length (k). The code has n = 2^r - 1 for r >= 2.
function calc_block_length (
constant k : natural;
ONE_PARITY_BIT : boolean := false)
return natural is
variable r : natural := 0;
begin -- function calc_nparity_bits
 
-- assert k > 0 report "Code construction not implement for message length 0." severity failure;
 
if ONE_PARITY_BIT then
return k + 1;
end if;
r := calc_nparity_bits(k);
 
return 2**r - 1;
end function calc_block_length;
 
procedure check_parameters (
constant BLOCK_LENGTH : in natural;
constant NPARITY_BITS : in natural;
constant MESSAGE_LENGTH : in natural;
constant EXTRA_PARITY_BIT : in natural;
constant ONE_PARITY_BIT : in boolean;
constant CORRECT : in boolean := false) is
begin
assert BLOCK_LENGTH = calc_block_length(MESSAGE_LENGTH, ONE_PARITY_BIT) report "Invalid parameter value BLOCK_LENGTH := " & natural'image(BLOCK_LENGTH) severity failure;
assert NPARITY_BITS = calc_nparity_bits(MESSAGE_LENGTH, ONE_PARITY_BIT) report "Invalid parameter value NPARITY_BITS := " & natural'image(NPARITY_BITS) severity failure;
 
if ONE_PARITY_BIT then
assert EXTRA_PARITY_BIT = 0 report "EXTRA_PARITY_BIT 1 is not compatible with ONE_PARITY_BIT true." severity failure;
assert CORRECT = false report "CORRECT true is not compatible with ONE_PARITY_BIT true." severity failure;
end if;
end procedure check_parameters;
 
end package body yahamm_pkg;

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.