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

Subversion Repositories astron_adder

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /
    from Rev 4 to Rev 5
    Reverse comparison

Rev 4 → Rev 5

/astron_adder/trunk/common_adder_tree.vhd
0,0 → 1,54
-------------------------------------------------------------------------------
--
-- 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;
 
-- Purpose: Parallel adder tree.
-- Description:
-- . Add g_nof_inputs from an input vector in_dat. The number of stages in the
-- adder tree is ceil_log2(g_nof_inputs). Each amount of pipelining per stage
-- is set by g_pipeline.
-- Remarks:
-- . Use ceil_log2(g_nof_inputs) instead of true_log2() for the number of
-- stages in the adder tree, to have also for g_nof_inputs = 1 one stage that
-- effectively adds 0 to the single in_dat. In this way this 'str'
-- architecture behaves the same as the 'recursive' architecture for
-- g_nof_inputs = 1. The 'recursive' architecture uses this one bit growth
-- for g_nof_inputs = 1 to match the bit growth of a parallel adder in the
-- same stage when g_nof_inputs is odd.
 
ENTITY common_adder_tree IS
GENERIC (
g_representation : STRING := "SIGNED";
g_pipeline : NATURAL := 1; -- amount of pipelining per stage
g_nof_inputs : NATURAL := 4; -- >= 1, nof stages = ceil_log2(g_nof_inputs)
g_dat_w : NATURAL := (12+16)+2;
g_sum_w : NATURAL := (12+16)+4 -- g_dat_w + ceil_log2(g_nof_inputs)
);
PORT (
clk : IN STD_LOGIC;
clken : IN STD_LOGIC := '1';
in_dat : IN STD_LOGIC_VECTOR(g_nof_inputs*g_dat_w-1 DOWNTO 0);
sum : OUT STD_LOGIC_VECTOR( g_sum_w-1 DOWNTO 0)
);
END common_adder_tree;
/astron_adder/trunk/common_adder_tree_a_str.vhd
0,0 → 1,158
-------------------------------------------------------------------------------
--
-- 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, common_pkg_lib, common_components_lib;
USE IEEE.std_logic_1164.ALL;
USE common_pkg_lib.common_pkg.ALL;
 
ARCHITECTURE str OF common_adder_tree IS
 
-- common_add_sub pipelining
CONSTANT c_pipeline_in : NATURAL := 0;
CONSTANT c_pipeline_out : NATURAL := g_pipeline;
-- There is no need to internally work with the adder tree sum width for
-- worst case bit growth of c_sum_w = g_dat_w+ceil_log2(g_nof_inputs),
-- because any MSbits that are not in the output sum do not need to be kept
-- at the internal stages either. The worst case bit growth for
-- g_nof_inputs = 1 still becomes ceil_log2(g_nof_inputs) = 1, which can be
-- regarded as due to an adder stage that adds 0 to the single in_dat.
-- However it also does not cause extra logic to internally account for bit
-- growth at every stage, because synthesis will optimize unused MSbits away
-- when g_sum_w < c_sum_w.
CONSTANT c_w : NATURAL := g_dat_w; -- input data width
CONSTANT c_sum_w : NATURAL := g_dat_w+ceil_log2(g_nof_inputs); -- adder tree sum width
CONSTANT c_N : NATURAL := g_nof_inputs; -- nof inputs to the adder tree
CONSTANT c_nof_stages : NATURAL := ceil_log2(c_N); -- nof stages in the adder tree
-- Allocate c_sum_w for each field and allocate c_N fields for the input
-- stage and use this array for all stages. Hence the stage vectors
-- are longer than necessary and wider than necessary, but that is OK, the
-- important thing is that they are sufficiently long.
TYPE t_stage_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_N*c_sum_w-1 DOWNTO 0);
SIGNAL adds : t_stage_arr(-1 TO c_nof_stages-1);
BEGIN
 
-- The tabel below lists how many two port adders (+) and one port pipes (.)
-- to match the adder latency, there are at each stage of the adder tree.
--
-- nof +,. nof +,. nof +,. nof +,. nof +,.
-- stage 0 stage 1 stage 2 stage 3 --> total
-- N = 2 1,0 - - - 1
-- 3 1,1 1,0 - - 3
-- 4 2,0 1,0 - - 3
-- 5 2,1 1,1 1,0 - 6
-- 6 3,0 1,1 1,0 - 6
-- 7 3,1 2,0 1,0 - 7
-- 8 4,0 2,0 1,0 - 7
-- 9 4,1 2,1 1,1 1,0 11 < N + nof stages
-- 10 5,0 2,1 1,1 1,0 11
-- 11 5,1 3,0 1,1 1,0 12
-- 12 6,0 3,0 1,1 1,0 12
-- 13 6,1 3,1 2,0 1,0 14
--
-- input output nof
-- stage nof + nof . width width input
-- - - - - w+0 -
-- 0 (N+0)/2 ((N+0)/1) MOD 2 w+0 w+1 N
-- 1 (N+1)/4 ((N+1)/2) MOD 2 w+1 w+2 (N+0)/2 + ((N+0)/1) MOD 2
-- 2 (N+3)/8 ((N+3)/4) MOD 2 w+2 w+3 (N+3)/8 + ((N+3)/4) MOD 2
-- 3 (N+7)/16 ((N+7)/8) MOD 2 w+3 w+4 (N+7)/16 + ((N+7)/8) MOD 2
--
-- j (N+(2**j)-1)/(2**(j+1)) ((N+(2**j)-1)/(2**j)) MOD 2 w+j w+j+1
-- Keep in_dat in stage -1 of adds. Store each subsequent stage of the adder
-- tree in into adds. Until finally the total sum in the last stage.
gen_tree : IF g_nof_inputs > 1 GENERATE
-- Input wires
adds(-1)(in_dat'RANGE) <= in_dat;
-- Adder tree
gen_stage : FOR j IN 0 TO c_nof_stages-1 GENERATE
gen_add : FOR i IN 0 TO (c_N+(2**j)-1)/(2**(j+1)) - 1 GENERATE
u_addj : ENTITY work.common_add_sub
GENERIC MAP (
g_direction => "ADD",
g_representation => g_representation,
g_pipeline_input => c_pipeline_in,
g_pipeline_output => c_pipeline_out,
g_in_dat_w => c_w+j,
g_out_dat_w => c_w+j+1
)
PORT MAP (
clk => clk,
clken => clken,
in_a => adds(j-1)((2*i+1)*(c_w+j)-1 DOWNTO (2*i+0)*(c_w+j)),
in_b => adds(j-1)((2*i+2)*(c_w+j)-1 DOWNTO (2*i+1)*(c_w+j)),
result => adds(j)((i+1)*(c_w+j+1)-1 DOWNTO i*(c_w+j+1))
);
END GENERATE;
gen_pipe : IF ((c_N+(2**j)-1)/(2**j)) MOD 2 /= 0 GENERATE
u_pipej : ENTITY common_components_lib.common_pipeline
GENERIC MAP (
g_representation => g_representation,
g_pipeline => g_pipeline,
g_in_dat_w => c_w+j,
g_out_dat_w => c_w+j+1
)
PORT MAP (
clk => clk,
clken => clken,
in_dat => adds(j-1)((2*((c_N+(2**j)-1)/(2**(j+1)))+1)*(c_w+j)-1 DOWNTO
(2*((c_N+(2**j)-1)/(2**(j+1)))+0)*(c_w+j)),
out_dat => adds(j)(((c_N+(2**j)-1)/(2**(j+1))+1)*(c_w+j+1)-1 DOWNTO
((c_N+(2**j)-1)/(2**(j+1)) )*(c_w+j+1))
);
END GENERATE;
END GENERATE;
-- Map final sum to larger output vector using sign extension or to smaller width output vector preserving the LS part
sum <= RESIZE_SVEC(adds(c_nof_stages-1)(c_sum_w-1 DOWNTO 0), g_sum_w) WHEN g_representation="SIGNED" ELSE
RESIZE_UVEC(adds(c_nof_stages-1)(c_sum_w-1 DOWNTO 0), g_sum_w);
END GENERATE; -- gen_tree
 
no_tree : IF g_nof_inputs = 1 GENERATE
-- For g_nof_inputs = 1 gen_tree yields wires sum <= in_dat, therefore
-- here use common_pipeline to support g_pipeline. Note c_sum_w =
-- g_dat_w+1 also for g_nof_inputs = 1, because we assume an adder stage
-- that adds 0 to the single in_dat.
u_reg : ENTITY common_components_lib.common_pipeline
GENERIC MAP (
g_representation => g_representation,
g_pipeline => g_pipeline,
g_in_dat_w => g_dat_w,
g_out_dat_w => g_sum_w
)
PORT MAP (
clk => clk,
clken => clken,
in_dat => in_dat,
out_dat => sum
);
END GENERATE; -- no_tree
END str;
/astron_adder/trunk/hdllib.cfg
6,13 → 6,20
 
synth_files =
common_add_sub.vhd
 
common_adder_tree.vhd
common_adder_tree_a_str.vhd
test_bench_files =
tb_common_add_sub.vhd
tb_tb_common_add_sub.vhd
 
tb_common_adder_tree.vhd
tb_tb_common_adder_tree.vhd
 
regression_test_vhdl =
tb_tb_common_add_sub.vhd
tb_tb_common_adder_tree.vhd
[modelsim_project_file]
modelsim_copy_files =
/astron_adder/trunk/tb_common_adder_tree.vhd
0,0 → 1,197
-------------------------------------------------------------------------------
--
-- 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/>.
--
-------------------------------------------------------------------------------
 
-- Usage:
-- > as 10
-- > run -all
-- . Observe in_data_arr_p and the expected result and the result of the DUT in the Wave window
-- . This TB verifies the DUT architecture that was compile last. Default after a fresh mk the (str)
-- is compiled last, to simulate the (recursive) manually compile it and the simulate again.
-- Within the recursive architecture it is not possible to explicitely configure it to recursively
-- use the recursive architecture using FOR ALL : ENTITY because the instance label is within a
-- generate block.
-- . The p_verify makes the tb self checking and asserts when the results are not equal
LIBRARY IEEE, common_pkg_lib, common_components_lib;
USE IEEE.std_logic_1164.ALL;
USE IEEE.numeric_std.ALL;
USE common_pkg_lib.common_pkg.ALL;
USE common_pkg_lib.tb_common_pkg.ALL;
 
 
ENTITY tb_common_adder_tree IS
GENERIC (
g_representation : STRING := "SIGNED";
g_pipeline : NATURAL := 1; -- amount of pipelining per stage
g_nof_inputs : NATURAL := 31; -- >= 1
g_symbol_w : NATURAL := 8;
g_sum_w : NATURAL := 8 -- worst case bit growth requires g_symbol_w + ceil_log2(g_nof_inputs);
);
END tb_common_adder_tree;
 
 
ARCHITECTURE tb OF tb_common_adder_tree IS
 
CONSTANT clk_period : TIME := 10 ns;
CONSTANT c_data_vec_w : NATURAL := g_nof_inputs*g_symbol_w;
CONSTANT c_nof_stages : NATURAL := ceil_log2(g_nof_inputs);
CONSTANT c_pipeline_tree : NATURAL := g_pipeline*c_nof_stages;
TYPE t_symbol_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_symbol_w-1 DOWNTO 0);
-- Use the same symbol value g_nof_inputs time in the data_vec
FUNCTION func_data_vec(symbol : INTEGER) RETURN STD_LOGIC_VECTOR IS
VARIABLE v_data_vec : STD_LOGIC_VECTOR(c_data_vec_w-1 DOWNTO 0);
BEGIN
FOR I IN 0 TO g_nof_inputs-1 LOOP
v_data_vec((I+1)*g_symbol_w-1 DOWNTO I*g_symbol_w) := TO_UVEC(symbol, g_symbol_w);
END LOOP;
RETURN v_data_vec;
END;
-- Calculate the expected result of the sum of the symbols in the data_vec
FUNCTION func_result(data_vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
VARIABLE v_result : INTEGER;
BEGIN
v_result := 0;
IF g_representation="SIGNED" THEN
FOR I IN 0 TO g_nof_inputs-1 LOOP
v_result := v_result + TO_SINT(data_vec((I+1)*g_symbol_w-1 DOWNTO I*g_symbol_w));
END LOOP;
v_result := RESIZE_SINT(v_result, g_sum_w);
RETURN TO_SVEC(v_result, g_sum_w);
ELSE
FOR I IN 0 TO g_nof_inputs-1 LOOP
v_result := v_result + TO_UINT(data_vec((I+1)*g_symbol_w-1 DOWNTO I*g_symbol_w));
END LOOP;
v_result := RESIZE_UINT(v_result, g_sum_w);
RETURN TO_UVEC(v_result, g_sum_w);
END IF;
END;
 
SIGNAL rst : STD_LOGIC;
SIGNAL clk : STD_LOGIC := '1';
SIGNAL tb_end : STD_LOGIC := '0';
SIGNAL result_comb : STD_LOGIC_VECTOR(g_sum_w-1 DOWNTO 0); -- expected combinatorial sum
SIGNAL in_data_vec : STD_LOGIC_VECTOR(c_data_vec_w-1 DOWNTO 0) := (OTHERS=>'0');
SIGNAL in_data_vec_p : STD_LOGIC_VECTOR(c_data_vec_w-1 DOWNTO 0);
SIGNAL in_data_arr_p : t_symbol_arr(0 TO g_nof_inputs-1);
SIGNAL result_expected : STD_LOGIC_VECTOR(g_sum_w-1 DOWNTO 0); -- expected pipelined sum
SIGNAL result_dut : STD_LOGIC_VECTOR(g_sum_w-1 DOWNTO 0); -- DUT sum
BEGIN
 
clk <= NOT clk OR tb_end AFTER clk_period/2;
rst <= '1', '0' AFTER clk_period*3;
p_stimuli : PROCESS
BEGIN
in_data_vec <= (OTHERS=>'0');
proc_common_wait_until_low(clk, rst);
proc_common_wait_some_cycles(clk, 5);
 
-- Apply equal symbol value inputs
FOR I IN 0 TO 2**g_symbol_w-1 LOOP
in_data_vec <= func_data_vec(I);
proc_common_wait_some_cycles(clk, 1);
END LOOP;
in_data_vec <= (OTHERS=>'0');
proc_common_wait_some_cycles(clk, 50);
tb_end <= '1';
WAIT;
END PROCESS;
-- For easier manual analysis in the wave window:
-- . Pipeline the in_data_vec to align with the result
-- . Map the concatenated symbols in in_data_vec into an in_data_arr_p array
u_data_vec_p : ENTITY common_components_lib.common_pipeline
GENERIC MAP (
g_representation => g_representation,
g_pipeline => c_pipeline_tree,
g_reset_value => 0,
g_in_dat_w => c_data_vec_w,
g_out_dat_w => c_data_vec_w
)
PORT MAP (
rst => rst,
clk => clk,
clken => '1',
in_dat => in_data_vec,
out_dat => in_data_vec_p
);
p_data_arr : PROCESS(in_data_vec_p)
BEGIN
FOR I IN 0 TO g_nof_inputs-1 LOOP
in_data_arr_p(I) <= in_data_vec_p((I+1)*g_symbol_w-1 DOWNTO I*g_symbol_w);
END LOOP;
END PROCESS;
result_comb <= func_result(in_data_vec);
u_result : ENTITY common_components_lib.common_pipeline
GENERIC MAP (
g_representation => g_representation,
g_pipeline => c_pipeline_tree,
g_reset_value => 0,
g_in_dat_w => g_sum_w,
g_out_dat_w => g_sum_w
)
PORT MAP (
rst => rst,
clk => clk,
clken => '1',
in_dat => result_comb,
out_dat => result_expected
);
-- Using work.common_adder_tree(recursive) will only invoke the recursive architecture once, because the next recursive level will default to using the last compiled architecture
-- Therefore only instatiatiate the DUT once in this tb and use compile order to influence which architecture is used.
dut : ENTITY work.common_adder_tree -- uses last compile architecture
GENERIC MAP (
g_representation => g_representation,
g_pipeline => g_pipeline,
g_nof_inputs => g_nof_inputs,
g_dat_w => g_symbol_w,
g_sum_w => g_sum_w
)
PORT MAP (
clk => clk,
in_dat => in_data_vec,
sum => result_dut
);
p_verify : PROCESS(rst, clk)
BEGIN
IF rst='0' THEN
IF rising_edge(clk) THEN
ASSERT result_dut = result_expected REPORT "Error: wrong result_dut" SEVERITY ERROR;
END IF;
END IF;
END PROCESS;
END tb;
/astron_adder/trunk/tb_tb_common_adder_tree.vhd
0,0 → 1,64
-------------------------------------------------------------------------------
--
-- 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, common_pkg_lib;
USE IEEE.std_logic_1164.ALL;
USE common_pkg_lib.common_pkg.ALL;
 
ENTITY tb_tb_common_adder_tree IS
END tb_tb_common_adder_tree;
 
ARCHITECTURE tb OF tb_tb_common_adder_tree IS
SIGNAL tb_end : STD_LOGIC := '0'; -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
BEGIN
-- Usage:
-- > as 4
-- > run -all
 
-- g_representation : STRING := "SIGNED";
-- g_pipeline : NATURAL := 1; -- amount of pipelining per stage
-- g_nof_inputs : NATURAL := 1; -- >= 1
-- g_symbol_w : NATURAL := 8;
-- g_sum_w : NATURAL := 8 -- worst case bit growth requires g_symbol_w + c_nof_stages;
gen_nof_inputs : FOR I IN 1 TO 31 GENERATE
-- SIGNED
s_pipe_0 : ENTITY work.tb_common_adder_tree GENERIC MAP ("SIGNED", 0, I, 8, 8+ceil_log2(I));
s_pipe_1 : ENTITY work.tb_common_adder_tree GENERIC MAP ("SIGNED", 1, I, 8, 8+ceil_log2(I));
s_pipe_2 : ENTITY work.tb_common_adder_tree GENERIC MAP ("SIGNED", 2, I, 8, 8+ceil_log2(I));
s_sum_w_0 : ENTITY work.tb_common_adder_tree GENERIC MAP ("SIGNED", 1, I, 8, 8);
s_sum_w_plus_1 : ENTITY work.tb_common_adder_tree GENERIC MAP ("SIGNED", 1, I, 8, 8+1);
s_sum_w_min_1 : ENTITY work.tb_common_adder_tree GENERIC MAP ("SIGNED", 1, I, 8, 8-1);
s_sum_w_wider : ENTITY work.tb_common_adder_tree GENERIC MAP ("SIGNED", 1, I, 8, 8+8);
-- UNSIGNED
u_pipe_0 : ENTITY work.tb_common_adder_tree GENERIC MAP ("UNSIGNED", 0, I, 8, 8+ceil_log2(I));
u_pipe_1 : ENTITY work.tb_common_adder_tree GENERIC MAP ("UNSIGNED", 1, I, 8, 8+ceil_log2(I));
u_pipe_2 : ENTITY work.tb_common_adder_tree GENERIC MAP ("UNSIGNED", 2, I, 8, 8+ceil_log2(I));
u_sum_w_0 : ENTITY work.tb_common_adder_tree GENERIC MAP ("UNSIGNED", 1, I, 8, 8);
u_sum_w_plus_1 : ENTITY work.tb_common_adder_tree GENERIC MAP ("UNSIGNED", 1, I, 8, 8+1);
u_sum_w_min_1 : ENTITY work.tb_common_adder_tree GENERIC MAP ("UNSIGNED", 1, I, 8, 8-1);
u_sum_w_wider : ENTITY work.tb_common_adder_tree GENERIC MAP ("UNSIGNED", 1, I, 8, 8+8);
END GENERATE;
END tb;

powered by: WebSVN 2.1.0

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