Skip to content
Snippets Groups Projects
Commit 49fae287 authored by Zanting's avatar Zanting
Browse files

Removed unported parts from library

parent 95a75925
No related branches found
No related tags found
No related merge requests found
-------------------------------------------------------------------------------
--
-- Copyright (C) 2009
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- 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 <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE;
USE IEEE.std_logic_1164.ALL;
USE IEEE.numeric_std.ALL;
USE work.common_pkg.ALL;
ENTITY tb_common_complex_mult_add_parallel IS
GENERIC (
g_nof_stages : NATURAL := 8;
g_in_dat_w : NATURAL := 16
);
END tb_common_complex_mult_add_parallel;
ARCHITECTURE tb OF tb_common_complex_mult_add_parallel IS
CONSTANT clk_period : TIME := 10 ns;
CONSTANT c_conjugate : boolean := FALSE;
CONSTANT c_prod_w : NATURAL := 2*g_in_dat_w+1;
CONSTANT c_sum_w : NATURAL := c_prod_w + ceil_log2(g_nof_stages);
CONSTANT c_pipeline : NATURAL := 1+ceil_log2(g_nof_stages);
CONSTANT c_max_p : INTEGER := 2**(g_in_dat_w-1)-1;
CONSTANT c_min : INTEGER := -c_max_p;
CONSTANT c_max_n : INTEGER := -2**(g_in_dat_w-1);
--
FUNCTION func_complex_mul(in_ar, in_ai, in_br, in_bi : STD_LOGIC_VECTOR; conjugate_b : BOOLEAN; str : STRING) RETURN STD_LOGIC_VECTOR IS
-- Function: Signed complex multiply
-- p = a * b when g_conjugate_b = FALSE
-- = (ar + j ai) * (br + j bi)
-- = ar*br - ai*bi + j ( ar*bi + ai*br)
--
-- p = a * conj(b) when g_conjugate_b = TRUE
-- = (ar + j ai) * (br - j bi)
-- = ar*br + ai*bi + j (-ar*bi + ai*br)
-- From mti_numeric_std.vhd follows:
-- . SIGNED * --> output width = 2 * input width
-- . SIGNED + --> output width = largest(input width)
CONSTANT c_in_w : NATURAL := g_in_dat_w;
CONSTANT c_res_w : NATURAL := 2*c_in_w+1; -- *2 for multiply, +1 for sum of two products
VARIABLE v_ar : SIGNED(c_in_w-1 DOWNTO 0);
VARIABLE v_ai : SIGNED(c_in_w-1 DOWNTO 0);
VARIABLE v_br : SIGNED(c_in_w-1 DOWNTO 0);
VARIABLE v_bi : SIGNED(c_in_w-1 DOWNTO 0);
VARIABLE v_result_re : SIGNED(c_res_w-1 DOWNTO 0);
VARIABLE v_result_im : SIGNED(c_res_w-1 DOWNTO 0);
BEGIN
-- Calculate expected result
v_ar := RESIZE_NUM(SIGNED(in_ar), c_in_w);
v_ai := RESIZE_NUM(SIGNED(in_ai), c_in_w);
v_br := RESIZE_NUM(SIGNED(in_br), c_in_w);
v_bi := RESIZE_NUM(SIGNED(in_bi), c_in_w);
IF conjugate_b=FALSE THEN
v_result_re := RESIZE_NUM(v_ar*v_br, c_res_w) - v_ai*v_bi;
v_result_im := RESIZE_NUM(v_ar*v_bi, c_res_w) + v_ai*v_br;
ELSE
v_result_re := RESIZE_NUM(v_ar*v_br, c_res_w) + v_ai*v_bi;
v_result_im := RESIZE_NUM(v_ai*v_br, c_res_w) - v_ar*v_bi;
END IF;
IF str="RE" THEN
RETURN STD_LOGIC_VECTOR(RESIZE_NUM(v_result_re, c_res_w));
ELSE
RETURN STD_LOGIC_VECTOR(RESIZE_NUM(v_result_im, c_res_w));
END IF;
END;
SIGNAL rst : STD_LOGIC;
SIGNAL clk : STD_LOGIC := '0';
TYPE t_slv_in_array IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); -- Type for input data array
TYPE t_slv_p_array IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(2*g_in_dat_w DOWNTO 0); -- Type for array of products
SIGNAL in_ar : t_slv_in_array(g_nof_stages-1 DOWNTO 0);
SIGNAL in_ai : t_slv_in_array(g_nof_stages-1 DOWNTO 0);
SIGNAL in_br : t_slv_in_array(g_nof_stages-1 DOWNTO 0);
SIGNAL in_bi : t_slv_in_array(g_nof_stages-1 DOWNTO 0);
SIGNAL in_ar_vec : STD_LOGIC_VECTOR(g_nof_stages*g_in_dat_w-1 DOWNTO 0);
SIGNAL in_ai_vec : STD_LOGIC_VECTOR(g_nof_stages*g_in_dat_w-1 DOWNTO 0);
SIGNAL in_br_vec : STD_LOGIC_VECTOR(g_nof_stages*g_in_dat_w-1 DOWNTO 0);
SIGNAL in_bi_vec : STD_LOGIC_VECTOR(g_nof_stages*g_in_dat_w-1 DOWNTO 0);
SIGNAL prod_r : t_slv_p_array(g_nof_stages-1 DOWNTO 0);
SIGNAL prod_i : t_slv_p_array(g_nof_stages-1 DOWNTO 0);
SIGNAL sum_r_d : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
SIGNAL sum_i_d : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
SIGNAL result_r_expected : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0); -- pipelined results
SIGNAL result_i_expected : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0); -- pipelined results
SIGNAL result_r : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
SIGNAL result_i : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
BEGIN
clk <= NOT clk AFTER clk_period/2;
-- run 1 us
p_in_stimuli : PROCESS
BEGIN
rst <= '1';
for I in 0 to g_nof_stages - 1 loop
in_ar(I) <= TO_SVEC(0, in_ar(I)'length);
in_ai(I) <= TO_SVEC(0, in_ar(I)'length);
in_br(I) <= TO_SVEC(0, in_ar(I)'length);
in_bi(I) <= TO_SVEC(0, in_ar(I)'length);
end loop;
WAIT UNTIL rising_edge(clk);
FOR I IN 0 TO 9 LOOP
WAIT UNTIL rising_edge(clk);
END LOOP;
rst <= '0';
FOR I IN 0 TO 9 LOOP
WAIT UNTIL rising_edge(clk);
END LOOP;
-- Some special combinations
FOR I IN 0 TO g_nof_stages - 1 LOOP
in_ar(I) <= TO_SVEC(2, in_ar(I)'length);
in_ai(I) <= TO_SVEC(3, in_ar(I)'length);
in_br(I) <= TO_SVEC(4, in_ar(I)'length);
in_bi(I) <= TO_SVEC(5, in_ar(I)'length);
END LOOP;
WAIT UNTIL rising_edge(clk);
-- Some special combinations
FOR I IN 0 TO g_nof_stages - 1 LOOP
in_ar(I) <= TO_SVEC(8, in_ar(I)'length);
in_ai(I) <= TO_SVEC(6, in_ar(I)'length);
in_br(I) <= TO_SVEC(7, in_ar(I)'length);
in_bi(I) <= TO_SVEC(4, in_ar(I)'length);
END LOOP;
WAIT UNTIL rising_edge(clk);
-- p*p + p*p = 2pp
FOR I IN 0 TO g_nof_stages - 1 LOOP
in_ar(I) <= TO_SVEC(c_max_p, in_ar(I)'length);
in_ai(I) <= TO_SVEC(c_max_p, in_ar(I)'length);
in_br(I) <= TO_SVEC(c_max_p, in_ar(I)'length);
in_bi(I) <= TO_SVEC(c_max_p, in_ar(I)'length);
END LOOP;
WAIT UNTIL rising_edge(clk);
-- -p*-p + -p*-p = -2pp
FOR I IN 0 TO g_nof_stages - 1 LOOP
in_ar(I) <= TO_SVEC(c_max_n, in_ar(I)'length);
in_ai(I) <= TO_SVEC(c_max_n, in_ar(I)'length);
in_br(I) <= TO_SVEC(c_max_n, in_ar(I)'length);
in_bi(I) <= TO_SVEC(c_max_n, in_ar(I)'length);
END LOOP;
WAIT UNTIL rising_edge(clk);
-- p*-p + p*-p = = -2pp
FOR I IN 0 TO g_nof_stages - 1 LOOP
in_ar(I) <= TO_SVEC(c_max_p, in_ar(I)'length);
in_ai(I) <= TO_SVEC(c_max_n, in_ar(I)'length);
in_br(I) <= TO_SVEC(c_max_p, in_ar(I)'length);
in_bi(I) <= TO_SVEC(c_max_n, in_ar(I)'length);
END LOOP;
WAIT UNTIL rising_edge(clk);
-- p*(-p-1)_ + p*(-p-1) = -(2pp + 2p)
FOR I IN 0 TO g_nof_stages - 1 LOOP
in_ar(I) <= TO_SVEC(c_max_p, in_ar(I)'length);
in_ai(I) <= TO_SVEC(c_min, in_ar(I)'length);
in_br(I) <= TO_SVEC(c_max_p, in_ar(I)'length);
in_bi(I) <= TO_SVEC(c_min, in_ar(I)'length);
END LOOP;
-- -p*(-p-1)_ + -p*(-p-1) = 2pp + 2p
FOR I IN 0 TO g_nof_stages - 1 LOOP
in_ar(I) <= TO_SVEC(c_max_n, in_ar(I)'length);
in_ai(I) <= TO_SVEC(c_min, in_ar(I)'length);
in_br(I) <= TO_SVEC(c_max_n, in_ar(I)'length);
in_bi(I) <= TO_SVEC(c_min, in_ar(I)'length);
END LOOP;
FOR I IN 0 TO 49 LOOP
WAIT UNTIL rising_edge(clk);
END LOOP;
-- All combinations
FOR I IN -2**(g_in_dat_w-1) TO 2**(g_in_dat_w-1)-1 LOOP
FOR J IN -2**(g_in_dat_w-1) TO 2**(g_in_dat_w-1)-1 LOOP
FOR K IN -2**(g_in_dat_w-1) TO 2**(g_in_dat_w-1)-1 LOOP
FOR L IN -2**(g_in_dat_w-1) TO 2**(g_in_dat_w-1)-1 LOOP
FOR M IN 0 TO g_nof_stages - 1 LOOP
in_ar(M) <= TO_SVEC(I, in_ar(M)'length);
in_ai(M) <= TO_SVEC(J, in_ar(M)'length);
in_br(M) <= TO_SVEC(K, in_ar(M)'length);
in_bi(M) <= TO_SVEC(L, in_ar(M)'length);
END LOOP;
WAIT UNTIL rising_edge(clk);
END LOOP;
END LOOP;
END LOOP;
END LOOP;
WAIT;
END PROCESS;
-- The tester calculates the expected output.
tester : PROCESS
VARIABLE sum_r : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
VARIABLE sum_i : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
BEGIN
WAIT UNTIL rising_edge(clk);
sum_r := (OTHERS => '0');
sum_i := (OTHERS => '0');
-- First all products are calculated
FOR I IN 0 TO g_nof_stages-1 LOOP
prod_r(I) <=func_complex_mul(in_ar(I), in_ai(I), in_br(I), in_bi(I), c_conjugate, "RE");
prod_i(I) <=func_complex_mul(in_ar(I), in_ai(I), in_br(I), in_bi(I), c_conjugate, "IM");
END LOOP;
-- Secondly all products are added.
FOR I IN 0 TO g_nof_stages-1 LOOP
sum_r := STD_LOGIC_VECTOR((SIGNED(sum_r) + SIGNED(prod_r(I))));
sum_i := STD_LOGIC_VECTOR((SIGNED(sum_i) + SIGNED(prod_i(I))));
END LOOP;
sum_r_d <= sum_r;
sum_i_d <= sum_i;
END PROCESS;
-- Add a number of pipeline stages to get in sync with the DUT.
-- For the real part:
u_result_re : ENTITY work.common_pipeline
GENERIC MAP (
g_representation => "SIGNED",
g_pipeline => c_pipeline,
g_reset_value => 0,
g_in_dat_w => c_sum_w,
g_out_dat_w => c_sum_w
)
PORT MAP (
rst => rst,
clk => clk,
clken => '1',
in_dat => sum_r_d,
out_dat => result_r_expected
);
-- And the imaginary part:
u_result_im : ENTITY work.common_pipeline
GENERIC MAP (
g_representation => "SIGNED",
g_pipeline => c_pipeline,
g_reset_value => 0,
g_in_dat_w => c_sum_w,
g_out_dat_w => c_sum_w
)
PORT MAP (
rst => rst,
clk => clk,
clken => '1',
in_dat => sum_i_d,
out_dat => result_i_expected
);
-- Wires are used to map the array of std_logic_vectors to the "large" input vectors.
-- In simulation it is easier to trace values in an array instead of the large vector.
wires : FOR I IN 0 TO g_nof_stages - 1 GENERATE
in_ar_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= in_ar(I);
in_ai_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= in_ai(I);
in_br_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= in_br(I);
in_bi_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= in_bi(I);
END GENERATE wires;
dut : ENTITY work.common_complex_mult_add_parallel
GENERIC MAP (
g_nof_stages => g_nof_stages,
g_in_a_w => g_in_dat_w,
g_in_b_w => g_in_dat_w,
g_out_w => c_sum_w
)
PORT MAP(
rst => rst,
clk => clk,
clken => '1',
in_ar => in_ar_vec,
in_ai => in_ai_vec,
in_br => in_br_vec,
in_bi => in_bi_vec,
out_sumr => result_r,
out_sumi => result_i
);
p_verify : PROCESS(rst, clk)
BEGIN
IF rst='0' THEN
IF rising_edge(clk) THEN
ASSERT result_r = result_r_expected REPORT "Error: wrong RTL result in real path" SEVERITY ERROR;
ASSERT result_i = result_i_expected REPORT "Error: wrong RTL result in imag path" SEVERITY ERROR;
END IF;
END IF;
END PROCESS;
END tb;
-------------------------------------------------------------------------------
--
-- Copyright (C) 2009
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- 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 <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE;
USE IEEE.std_logic_1164.ALL;
USE IEEE.numeric_std.ALL;
USE work.common_pkg.ALL;
ENTITY tb_common_complex_mult_add_pipeline IS
GENERIC (
g_nof_stages : NATURAL := 4;
g_in_dat_w : NATURAL := 16;
g_ch_dat_w : NATURAL := 38;
g_out_dat_w : NATURAL := 38;
g_pipeline_input : NATURAL := 1;
g_pipeline_product : NATURAL := 0;
g_pipeline_adder : NATURAL := 1;
g_pipeline_output : NATURAL := 1
);
END tb_common_complex_mult_add_pipeline;
ARCHITECTURE tb OF tb_common_complex_mult_add_pipeline IS
CONSTANT clk_period : TIME := 10 ns;
CONSTANT c_conjugate : boolean := FALSE;
CONSTANT c_prod_w : NATURAL := 2*g_in_dat_w+1;
CONSTANT c_sum_w : NATURAL := c_prod_w + ceil_log2(g_nof_stages);
-- CONSTANT c_pipeline : NATURAL := g_pipeline_input + g_pipeline_product + g_pipeline_adder + g_pipeline_output;
-- CONSTANT c_nof_mult : NATURAL := 2; -- fixed
--
-- CONSTANT c_max_p : INTEGER := 2**(g_in_dat_w-1)-1;
-- CONSTANT c_min : INTEGER := -c_max_p;
-- CONSTANT c_max_n : INTEGER := -2**(g_in_dat_w-1);
--
FUNCTION func_complex_mul(in_ar, in_ai, in_br, in_bi : STD_LOGIC_VECTOR; conjugate_b : BOOLEAN; str : STRING) RETURN STD_LOGIC_VECTOR IS
-- Function: Signed complex multiply
-- p = a * b when g_conjugate_b = FALSE
-- = (ar + j ai) * (br + j bi)
-- = ar*br - ai*bi + j ( ar*bi + ai*br)
--
-- p = a * conj(b) when g_conjugate_b = TRUE
-- = (ar + j ai) * (br - j bi)
-- = ar*br + ai*bi + j (-ar*bi + ai*br)
-- From mti_numeric_std.vhd follows:
-- . SIGNED * --> output width = 2 * input width
-- . SIGNED + --> output width = largest(input width)
CONSTANT c_in_w : NATURAL := g_in_dat_w;
CONSTANT c_res_w : NATURAL := g_out_dat_w; -- 2*g_in_dat_w+1; -- *2 for multiply, +1 for sum of two products
VARIABLE v_ar : SIGNED(c_in_w-1 DOWNTO 0);
VARIABLE v_ai : SIGNED(c_in_w-1 DOWNTO 0);
VARIABLE v_br : SIGNED(c_in_w-1 DOWNTO 0);
VARIABLE v_bi : SIGNED(c_in_w-1 DOWNTO 0);
VARIABLE v_result_re : SIGNED(c_res_w-1 DOWNTO 0);
VARIABLE v_result_im : SIGNED(c_res_w-1 DOWNTO 0);
BEGIN
-- Calculate expected result
v_ar := RESIZE_NUM(SIGNED(in_ar), c_in_w);
v_ai := RESIZE_NUM(SIGNED(in_ai), c_in_w);
v_br := RESIZE_NUM(SIGNED(in_br), c_in_w);
v_bi := RESIZE_NUM(SIGNED(in_bi), c_in_w);
IF conjugate_b=FALSE THEN
v_result_re := RESIZE_NUM(v_ar*v_br, c_res_w) - v_ai*v_bi;
v_result_im := RESIZE_NUM(v_ar*v_bi, c_res_w) + v_ai*v_br;
ELSE
v_result_re := RESIZE_NUM(v_ar*v_br, c_res_w) + v_ai*v_bi;
v_result_im := RESIZE_NUM(v_ai*v_br, c_res_w) - v_ar*v_bi;
END IF;
IF str="RE" THEN
RETURN STD_LOGIC_VECTOR(RESIZE_NUM(v_result_re, c_res_w));
ELSE
RETURN STD_LOGIC_VECTOR(RESIZE_NUM(v_result_im, c_res_w));
END IF;
END;
FUNCTION func_add(in_a, in_b :std_logic_vector) return std_logic_vector is
VARIABLE v_a : integer;
VARIABLE v_b : integer;
VARIABLE v_result : integer;
BEGIN
v_a := TO_SINT(in_a);
v_b := TO_SINT(in_b);
v_result := v_a + v_b;
RETURN TO_SVEC(v_result, g_out_dat_w);
END;
SIGNAL rst : STD_LOGIC;
SIGNAL clk : STD_LOGIC := '0';
TYPE t_slv_in_array IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); -- Type for input data array
TYPE t_slv_p_array IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_prod_w-1 DOWNTO 0); -- Type for array of products
TYPE t_slv_s_array IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0); -- Type for sums
SIGNAL in_ar : t_slv_in_array(g_nof_stages-1 DOWNTO 0);
SIGNAL in_ai : t_slv_in_array(g_nof_stages-1 DOWNTO 0);
SIGNAL in_br : t_slv_in_array(g_nof_stages-1 DOWNTO 0);
SIGNAL in_bi : t_slv_in_array(g_nof_stages-1 DOWNTO 0);
SIGNAL in_ar_vec : STD_LOGIC_VECTOR(g_nof_stages*g_in_dat_w-1 DOWNTO 0);
SIGNAL in_ai_vec : STD_LOGIC_VECTOR(g_nof_stages*g_in_dat_w-1 DOWNTO 0);
SIGNAL in_br_vec : STD_LOGIC_VECTOR(g_nof_stages*g_in_dat_w-1 DOWNTO 0);
SIGNAL in_bi_vec : STD_LOGIC_VECTOR(g_nof_stages*g_in_dat_w-1 DOWNTO 0);
SIGNAL prod_r : t_slv_p_array(g_nof_stages DOWNTO 0);
SIGNAL prod_i : t_slv_p_array(g_nof_stages DOWNTO 0);
SIGNAL sum_r : t_slv_s_array(g_nof_stages DOWNTO 0);
SIGNAL sum_i : t_slv_s_array(g_nof_stages DOWNTO 0);
SIGNAL sum_r_d1 : t_slv_s_array(g_nof_stages DOWNTO 0);
SIGNAL sum_i_d1 : t_slv_s_array(g_nof_stages DOWNTO 0);
SIGNAL sum_r_d2 : t_slv_s_array(g_nof_stages DOWNTO 0);
SIGNAL sum_i_d2 : t_slv_s_array(g_nof_stages DOWNTO 0);
SIGNAL result_r_expected : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
SIGNAL result_i_expected : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
SIGNAL result_r : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
SIGNAL result_i : STD_LOGIC_VECTOR(c_sum_w-1 DOWNTO 0);
BEGIN
clk <= NOT clk AFTER clk_period/2;
-- run 1 us
p_in_stimuli : PROCESS
BEGIN
rst <= '1';
for I in 0 to g_nof_stages - 1 loop
in_ar(I) <= TO_SVEC(0, in_ar(I)'length);
in_ai(I) <= TO_SVEC(0, in_ar(I)'length);
in_br(I) <= TO_SVEC(0, in_ar(I)'length);
in_bi(I) <= TO_SVEC(0, in_ar(I)'length);
end loop;
WAIT UNTIL rising_edge(clk);
FOR I IN 0 TO 9 LOOP
WAIT UNTIL rising_edge(clk);
END LOOP;
rst <= '0';
FOR I IN 0 TO 9 LOOP
WAIT UNTIL rising_edge(clk);
END LOOP;
-- Some special combinations
FOR I IN 0 TO g_nof_stages - 1 LOOP
in_ar(I) <= TO_SVEC(2, in_ar(I)'length);
in_ai(I) <= TO_SVEC(3, in_ar(I)'length);
in_br(I) <= TO_SVEC(4, in_ar(I)'length);
in_bi(I) <= TO_SVEC(5, in_ar(I)'length);
END LOOP;
WAIT UNTIL rising_edge(clk);
-- in_a0 <= TO_SVEC(c_max_p, g_in_dat_w); -- p*p + p*p = 2pp
-- in_b0 <= TO_SVEC(c_max_p, g_in_dat_w);
-- in_a1 <= TO_SVEC(c_max_p, g_in_dat_w);
-- in_b1 <= TO_SVEC(c_max_p, g_in_dat_w);
-- WAIT UNTIL rising_edge(clk);
-- in_a0 <= TO_SVEC(c_max_n, g_in_dat_w); -- -p*-p + -p*-p = -2pp
-- in_b0 <= TO_SVEC(c_max_n, g_in_dat_w);
-- in_a1 <= TO_SVEC(c_max_n, g_in_dat_w);
-- in_b1 <= TO_SVEC(c_max_n, g_in_dat_w);
-- WAIT UNTIL rising_edge(clk);
-- in_a0 <= TO_SVEC(c_max_p, g_in_dat_w); -- p*-p + p*-p = = -2pp
-- in_b0 <= TO_SVEC(c_max_n, g_in_dat_w);
-- in_a1 <= TO_SVEC(c_max_p, g_in_dat_w);
-- in_b1 <= TO_SVEC(c_max_n, g_in_dat_w);
-- WAIT UNTIL rising_edge(clk);
-- in_a0 <= TO_SVEC(c_max_p, g_in_dat_w); -- p*(-p-1)_ + p*(-p-1) = -(2pp + 2p)
-- in_b0 <= TO_SVEC(c_min, g_in_dat_w);
-- in_a1 <= TO_SVEC(c_max_p, g_in_dat_w);
-- in_b1 <= TO_SVEC(c_min, g_in_dat_w);
-- WAIT UNTIL rising_edge(clk);
-- in_a0 <= TO_SVEC(c_max_n, g_in_dat_w); -- -p*(-p-1)_ + -p*(-p-1) = 2pp + 2p
-- in_b0 <= TO_SVEC(c_min, g_in_dat_w);
-- in_a1 <= TO_SVEC(c_max_n, g_in_dat_w);
-- in_b1 <= TO_SVEC(c_min, g_in_dat_w);
-- WAIT UNTIL rising_edge(clk);
--
-- FOR I IN 0 TO 49 LOOP
-- WAIT UNTIL rising_edge(clk);
-- END LOOP;
--
-- -- All combinations
-- FOR I IN -2**(g_in_dat_w-1) TO 2**(g_in_dat_w-1)-1 LOOP
-- FOR J IN -2**(g_in_dat_w-1) TO 2**(g_in_dat_w-1)-1 LOOP
-- FOR K IN -2**(g_in_dat_w-1) TO 2**(g_in_dat_w-1)-1 LOOP
-- FOR L IN -2**(g_in_dat_w-1) TO 2**(g_in_dat_w-1)-1 LOOP
-- in_a0 <= TO_SVEC(I, g_in_dat_w);
-- in_b0 <= TO_SVEC(J, g_in_dat_w);
-- in_a1 <= TO_SVEC(K, g_in_dat_w);
-- in_b1 <= TO_SVEC(L, g_in_dat_w);
-- WAIT UNTIL rising_edge(clk);
-- END LOOP;
-- END LOOP;
-- END LOOP;
-- END LOOP;
WAIT;
END PROCESS;
prod_r(0) <= (OTHERS => '0');
prod_i(0) <= (OTHERS => '0');
tester : PROCESS
BEGIN
WAIT UNTIL rising_edge(clk);
FOR I IN 1 TO g_nof_stages LOOP
prod_r(I) <= RESIZE_SVEC(func_complex_mul(in_ar(I-1), in_ai(I-1), in_br(I-1), in_bi(I-1), c_conjugate, "RE"), c_prod_w);
prod_i(I) <= RESIZE_SVEC(func_complex_mul(in_ar(I-1), in_ai(I-1), in_br(I-1), in_bi(I-1), c_conjugate, "IM"), c_prod_w);
sum_r(I) <= RESIZE_SVEC(func_add(prod_r(I), sum_r(I-1)), c_sum_w);
sum_i(I) <= RESIZE_SVEC(func_add(prod_i(I), sum_i(I-1)), c_sum_w);
sum_r_d1(I) <= sum_r(I);
sum_i_d1(I) <= sum_i(I);
sum_r_d2(I) <= sum_r_d1(I);
sum_i_d2(I) <= sum_i_d1(I);
END LOOP;
END PROCESS;
result_r_expected <= sum_r_d2(g_nof_stages);
result_i_expected <= sum_i_d2(g_nof_stages);
-- Wires are used to map the array of std_logic_vectors to the "large" input vectors.
-- In simulation it is easier to trace values in an array instead of the large vector.
wires : FOR I IN 0 TO g_nof_stages - 1 GENERATE
in_ar_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= in_ar(I);
in_ai_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= in_ai(I);
in_br_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= in_br(I);
in_bi_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= in_bi(I);
END GENERATE wires;
u_dut_rtl : ENTITY work.common_complex_mult_add_pipeline(rtl)
GENERIC MAP (
g_nof_stages => g_nof_stages,
g_in_a_w => g_in_dat_w,
g_in_b_w => g_in_dat_w,
g_out_p_w => c_sum_w
)
PORT MAP (
rst => '0',
clk => clk,
clken => '1',
in_ar => in_ar_vec,
in_ai => in_ai_vec,
in_br => in_br_vec,
in_bi => in_bi_vec,
out_sumr => result_r,
out_sumi => result_i
);
p_verify : PROCESS(rst, clk)
BEGIN
IF rst='0' THEN
IF rising_edge(clk) THEN
ASSERT result_r = result_r_expected REPORT "Error: wrong RTL result in real path" SEVERITY ERROR;
ASSERT result_i = result_i_expected REPORT "Error: wrong RTL result in imag path" SEVERITY ERROR;
END IF;
END IF;
END PROCESS;
END tb;
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment