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

Subversion Repositories astron_statistics

Compare Revisions

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

Rev 1 → Rev 2

/hdllib.cfg
0,0 → 1,27
hdl_lib_name = statistics
hdl_library_clause_name = statistics_lib
hdl_lib_uses_synth = common_pkg common_components common_counter common_ram common_add_sub common_mult technology dp_pkg mm diag
hdl_lib_uses_sim =
hdl_lib_technology =
 
synth_files =
st_acc.vhd
st_ctrl.vhd
st_calc.vhd
st_sst.vhd
test_bench_files =
tb_st_acc.vhd
tb_st_calc.vhd
tb_mmf_st_sst.vhd
 
regression_test_vhdl =
tb_st_acc.vhd
#tb/vhdl/tb_st_calc.vhd -- tb is not self checking yet
 
 
[modelsim_project_file]
 
 
[quartus_project_file]
 
hdllib.cfg Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: st_acc.vhd =================================================================== --- st_acc.vhd (nonexistent) +++ st_acc.vhd (revision 2) @@ -0,0 +1,179 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib, common_components_lib, common_add_sub_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; + + +-- Purpose: +-- Accumulate input data to an accumulator that is stored externally. In this +-- way blocks of input samples (e.g. subband products) can be accumulated to +-- a set of external accumulators. At the in_load the accumulator input value +-- is ignored so that the accumulation restarts with the in_dat. +-- +-- Description: +-- if in_load = '1' then +-- out_acc = in_dat + 0 -- restart accumulation +-- else +-- out_acc = in_dat + in_acc -- accumulate +-- +-- Remarks: +-- . in_val propagates to out_val after the pipeline latency but does not +-- affect the sum + +ENTITY st_acc IS + GENERIC ( + g_dat_w : NATURAL; + g_acc_w : NATURAL; -- g_acc_w >= g_dat_w + g_hold_load : BOOLEAN := TRUE; + g_pipeline_input : NATURAL; -- 0 no input registers, else register input after in_load + g_pipeline_output : NATURAL -- pipeline for the adder + ); + PORT ( + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + in_load : IN STD_LOGIC; + in_dat : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + in_acc : IN STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0); + in_val : IN STD_LOGIC := '1'; + out_acc : OUT STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0); + out_val : OUT STD_LOGIC + ); +END st_acc; + + +ARCHITECTURE rtl OF st_acc IS + + CONSTANT c_pipeline : NATURAL := g_pipeline_input + g_pipeline_output; + + -- Input signals + SIGNAL hld_load : STD_LOGIC := '0'; + SIGNAL nxt_hld_load : STD_LOGIC; + SIGNAL acc_clr : STD_LOGIC; + + SIGNAL reg_dat : STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0) := (OTHERS=>'0'); + SIGNAL nxt_reg_dat : STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0); + SIGNAL reg_acc : STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0) := (OTHERS=>'0'); + SIGNAL nxt_reg_acc : STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0); + + -- Pipeline control signals, map to slv to be able to use common_pipeline + SIGNAL in_val_slv : STD_LOGIC_VECTOR(0 DOWNTO 0); + SIGNAL out_val_slv : STD_LOGIC_VECTOR(0 DOWNTO 0); + +BEGIN + + ASSERT NOT(g_acc_w < g_dat_w) + REPORT "st_acc: output accumulator width must be >= input data width" + SEVERITY FAILURE; + + ------------------------------------------------------------------------------ + -- Input load control + ------------------------------------------------------------------------------ + + p_clk : PROCESS(clk) + BEGIN + IF rising_edge(clk) THEN + IF clken='1' THEN + hld_load <= nxt_hld_load; + END IF; + END IF; + END PROCESS; + + nxt_hld_load <= in_load WHEN in_val='1' ELSE hld_load; + + -- Hold in_load to save power by avoiding unneccessary out_acc toggling when in_val goes low + -- . For g_pipeline_input>0 this is fine + -- . For g_pipeline_input=0 this may cause difficulty in achieving timing closure for synthesis + use_in_load : IF g_hold_load = FALSE GENERATE + acc_clr <= in_load; -- the in_load may already be extended during in_val + END GENERATE; + use_hld_load : IF g_hold_load = TRUE GENERATE + acc_clr <= in_load OR (hld_load AND NOT in_val); + END GENERATE; + + -- Do not use g_pipeline_input of u_adder, to allow registered acc clear if g_pipeline_input=1 + nxt_reg_dat <= RESIZE_SVEC(in_dat, g_acc_w); + nxt_reg_acc <= in_acc WHEN acc_clr='0' ELSE (OTHERS=>'0'); + + no_input_reg : IF g_pipeline_input=0 GENERATE + reg_dat <= nxt_reg_dat; + reg_acc <= nxt_reg_acc; + END GENERATE; + gen_input_reg : IF g_pipeline_input>0 GENERATE + p_reg : PROCESS(clk) + BEGIN + IF rising_edge(clk) THEN + IF clken='1' THEN + reg_dat <= nxt_reg_dat; + reg_acc <= nxt_reg_acc; + END IF; + END IF; + END PROCESS; + END GENERATE; + + + ------------------------------------------------------------------------------ + -- Adder for the external accumulator + ------------------------------------------------------------------------------ + + u_adder : ENTITY common_add_sub_lib.common_add_sub + GENERIC MAP ( + g_direction => "ADD", + g_representation => "SIGNED", -- not relevant because g_out_dat_w = g_in_dat_w + g_pipeline_input => 0, + g_pipeline_output => g_pipeline_output, + g_in_dat_w => g_acc_w, + g_out_dat_w => g_acc_w + ) + PORT MAP ( + clk => clk, + clken => clken, + in_a => reg_dat, + in_b => reg_acc, + result => out_acc + ); + + + ------------------------------------------------------------------------------ + -- Parallel output control pipeline + ------------------------------------------------------------------------------ + + in_val_slv(0) <= in_val; + out_val <= out_val_slv(0); + + u_out_val : ENTITY common_components_lib.common_pipeline + GENERIC MAP ( + g_representation => "UNSIGNED", + g_pipeline => c_pipeline, + g_reset_value => 0, + g_in_dat_w => 1, + g_out_dat_w => 1 + ) + PORT MAP ( + clk => clk, + clken => clken, + in_dat => slv(in_val), + out_dat => out_val_slv + ); + +END rtl;
st_acc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: st_calc.vhd =================================================================== --- st_calc.vhd (nonexistent) +++ st_calc.vhd (revision 2) @@ -0,0 +1,304 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib, common_ram_lib, common_mult_lib, technology_lib; +USE IEEE.std_logic_1164.ALL; +USE technology_lib.technology_select_pkg.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; + +-- Purpose: +-- Maintain a set of accumulators and output their values at every in_sync. +-- Description: +-- . The products of two input streams are accumulated per block. The block +-- size is g_nof_mux*g_nof_stat. The nof accumulators is equal to the block +-- size. The nof blocks that get accumulated depends on in_sync, because a +-- new accumulation starts every time when in_sync pulses. Also when in_sync +-- pulses then after some latency the accumulation values of the previous +-- in_sync interval become available at the out_* ports. +-- . If g_complex = FALSE then only the real power statistic out_re is calculated, +-- else also the imaginary power statistic out_im. The real power statistic +-- is used for auto power calulations of a complex input, by connecting the +-- signal to both input a and b. The imaginary is power statistic is used when +-- the cross power needs to be calculated between 2 different complex inputs. +-- Remarks: +-- . The required accumulator width depends the input data width and the nof of +-- block, i.e. the nof accumulations. E.g. for 18b*18b = 36b products and +-- 200000 accumulations yielding 18b bit growth so in total 36b+18b = 54b for +-- the accumulators. +-- . The nof accumulators determines the size (c_mem_acc) of the internal +-- accumulator memory. +-- . Using g_nof_mux>1 allows distinghuising different streams with a block. +-- The g_nof_mux does not impact the address range instead it impacts the +-- out_val_m strobes that can be used as wr_en to the corresponding statistics +-- output register in a range of g_nof_mux statistics output registers. + +ENTITY st_calc IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_nof_mux : NATURAL := 1; + g_nof_stat : NATURAL := 512; + g_in_dat_w : NATURAL := 18; -- = input data width + g_out_dat_w : NATURAL := 54; -- = accumulator width for the input data products, so >> 2*g_in_dat_w + g_out_adr_w : NATURAL := 9; -- = ceil_log2(g_nof_stat) + g_complex : BOOLEAN := FALSE + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + in_ar : IN STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + in_ai : IN STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + in_br : IN STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + in_bi : IN STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + in_val : IN STD_LOGIC; + in_sync : IN STD_LOGIC; + out_adr : OUT STD_LOGIC_VECTOR(g_out_adr_w-1 DOWNTO 0); + out_re : OUT STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); + out_im : OUT STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); + out_val : OUT STD_LOGIC; -- Use when g_nof_mux = 1, else leave OPEN + out_val_m : OUT STD_LOGIC_VECTOR(g_nof_mux-1 DOWNTO 0) -- Use when g_nof_mux > 1, else leave OPEN + ); +END; + + +ARCHITECTURE str OF st_calc IS + + CONSTANT c_mux_w : NATURAL := true_log2(g_nof_mux); + CONSTANT c_adr_w : NATURAL := c_mux_w+g_out_adr_w; -- = = ceil_log2(g_nof_mux*g_nof_stat) + + CONSTANT c_dly_rd : NATURAL := 2; + CONSTANT c_dly_mul : NATURAL := 3; + CONSTANT c_dly_acc : NATURAL := 2; + CONSTANT c_dly_out : NATURAL := 0; + + CONSTANT c_mult_w : NATURAL := 2*g_in_dat_w; + + CONSTANT c_acc_w : NATURAL := g_out_dat_w; + CONSTANT c_acc_hold_load : BOOLEAN := TRUE; + + CONSTANT c_rd_latency : NATURAL := 2; + CONSTANT c_mem_acc : t_c_mem := (c_rd_latency, c_adr_w, c_acc_w, g_nof_mux*g_nof_stat, 'X'); -- 1 M9K + + + SIGNAL mult_re : STD_LOGIC_VECTOR(c_mult_w-1 DOWNTO 0); + SIGNAL mult_im : STD_LOGIC_VECTOR(c_mult_w-1 DOWNTO 0); + + SIGNAL reg_ar : STD_LOGIC_VECTOR(in_ar'RANGE); + SIGNAL reg_ai : STD_LOGIC_VECTOR(in_ai'RANGE); + SIGNAL reg_br : STD_LOGIC_VECTOR(in_br'RANGE); + SIGNAL reg_bi : STD_LOGIC_VECTOR(in_bi'RANGE); + SIGNAL reg_val : STD_LOGIC; + SIGNAL reg_sync : STD_LOGIC; + + SIGNAL nxt_reg_ar : STD_LOGIC_VECTOR(in_ar'RANGE); + SIGNAL nxt_reg_ai : STD_LOGIC_VECTOR(in_ai'RANGE); + SIGNAL nxt_reg_br : STD_LOGIC_VECTOR(in_br'RANGE); + SIGNAL nxt_reg_bi : STD_LOGIC_VECTOR(in_bi'RANGE); + SIGNAL nxt_reg_val : STD_LOGIC; + SIGNAL nxt_reg_sync : STD_LOGIC; + + SIGNAL acc_load : STD_LOGIC; + + SIGNAL rd_en : STD_LOGIC; + SIGNAL rd_adr : STD_LOGIC_VECTOR(c_adr_w-1 DOWNTO 0); + SIGNAL rd_re : STD_LOGIC_VECTOR(c_acc_w-1 DOWNTO 0); + SIGNAL rd_im : STD_LOGIC_VECTOR(c_acc_w-1 DOWNTO 0); + + SIGNAL wr_en : STD_LOGIC; + SIGNAL wr_adr : STD_LOGIC_VECTOR(c_adr_w-1 DOWNTO 0); + SIGNAL wr_re : STD_LOGIC_VECTOR(c_acc_w-1 DOWNTO 0); + SIGNAL wr_im : STD_LOGIC_VECTOR(c_acc_w-1 DOWNTO 0); + + SIGNAL out_adr_m : STD_LOGIC_VECTOR(c_adr_w-1 DOWNTO 0); + +BEGIN + + regs: PROCESS(rst,clk) + BEGIN + IF rst='1' THEN + reg_ar <= (OTHERS => '0'); + reg_ai <= (OTHERS => '0'); + reg_br <= (OTHERS => '0'); + reg_bi <= (OTHERS => '0'); + reg_val <= '0'; + reg_sync <= '0'; + ELSIF rising_edge(clk) THEN + reg_ar <= nxt_reg_ar; + reg_ai <= nxt_reg_ai; + reg_br <= nxt_reg_br; + reg_bi <= nxt_reg_bi; + reg_val <= nxt_reg_val; + reg_sync <= nxt_reg_sync; + END IF; + END PROCESS; + + nxt_reg_ar <= in_ar WHEN in_val='1' ELSE reg_ar; + nxt_reg_ai <= in_ai WHEN in_val='1' ELSE reg_ai; + nxt_reg_br <= in_br WHEN in_val='1' ELSE reg_br; + nxt_reg_bi <= in_bi WHEN in_val='1' ELSE reg_bi; + nxt_reg_val <= in_val; + nxt_reg_sync <= in_sync; + + -- ctrl block: generates all ctrl signals + ctrl: ENTITY work.st_ctrl + GENERIC MAP ( + g_nof_mux => g_nof_mux, + g_nof_stat => g_nof_stat, + g_adr_w => c_adr_w, + g_dly_rd => c_dly_rd, + g_dly_mul => c_dly_mul, + g_dly_acc => c_dly_acc, + g_dly_out => c_dly_out + ) + PORT MAP ( + rst => rst, + clk => clk, + in_sync => reg_sync, + in_val => reg_val, + rd_en => rd_en, + rd_adr => rd_adr, + rd_val => OPEN, + mult_val => OPEN, + acc_load => acc_load, + wr_en => wr_en, + wr_adr => wr_adr, + out_val => out_val, + out_val_m => out_val_m, + out_adr => out_adr_m + ); + + out_adr <= out_adr_m(c_adr_w-1 DOWNTO c_mux_w); + + -- complex multiplier: computes a * conj(b) + --mul: ENTITY common_lib.common_complex_mult(str) + mul: ENTITY common_mult_lib.common_complex_mult + GENERIC MAP ( + g_technology => g_technology, + g_variant => "IP", + g_in_a_w => in_ar'LENGTH, + g_in_b_w => in_br'LENGTH, + g_out_p_w => mult_re'LENGTH, + g_conjugate_b => TRUE, -- use conjugate product for cross power + g_pipeline_input => 1, + g_pipeline_product => 0, + g_pipeline_adder => 1, + g_pipeline_output => 1 -- 1+0+1+1 = 3 = c_dly_mul + ) + PORT MAP ( + clk => clk, + clken => clken, + in_ar => reg_ar, + in_ai => reg_ai, + in_br => reg_br, + in_bi => reg_bi, + out_pr => mult_re, + out_pi => mult_im + ); + + -- accumulator for real part + acc_re: ENTITY work.st_acc + GENERIC MAP ( + g_dat_w => c_mult_w, + g_acc_w => c_acc_w, + g_hold_load => c_acc_hold_load, + g_pipeline_input => 1, + g_pipeline_output => c_dly_acc-1 + ) + PORT MAP ( + clk => clk, + clken => clken, + in_load => acc_load, + in_dat => mult_re, + in_acc => rd_re, + out_acc => wr_re + ); + + -- accumulator memory for real part + ram_re: ENTITY common_ram_lib.common_ram_r_w + GENERIC MAP ( + g_technology => g_technology, + g_ram => c_mem_acc, + g_init_file => "UNUSED" + ) + PORT MAP ( + rst => rst, + clk => clk, + clken => clken, + wr_en => wr_en, + wr_adr => wr_adr, + wr_dat => wr_re, + rd_en => rd_en, + rd_adr => rd_adr, + rd_dat => rd_re, + rd_val => OPEN + ); + + out_re <= rd_re; -- c_dly_out = 0 + + -- imaginary part is optional + no_im: IF g_complex=FALSE GENERATE + out_im <= (OTHERS => '0'); + END GENERATE; + + gen_im: IF g_complex=TRUE GENERATE + -- accumulator + acc_im: ENTITY work.st_acc + GENERIC MAP ( + g_dat_w => c_mult_w, + g_acc_w => c_acc_w, + g_hold_load => c_acc_hold_load, + g_pipeline_input => 1, + g_pipeline_output => c_dly_acc-1 + ) + PORT MAP ( + clk => clk, + clken => clken, + in_load => acc_load, + in_dat => mult_im, + in_acc => rd_im, + out_acc => wr_im + ); + + -- dual port memory + ram_im: ENTITY common_ram_lib.common_ram_r_w + GENERIC MAP ( + g_technology => g_technology, + g_ram => c_mem_acc, + g_init_file => "UNUSED" + ) + PORT MAP ( + rst => rst, + clk => clk, + clken => clken, + wr_en => wr_en, + wr_adr => wr_adr, + wr_dat => wr_im, + rd_en => rd_en, + rd_adr => rd_adr, + rd_dat => rd_im, + rd_val => OPEN + ); + + out_im <= rd_im; -- c_dly_out = 0 + END GENERATE; + +END str;
st_calc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: st_ctrl.vhd =================================================================== --- st_ctrl.vhd (nonexistent) +++ st_ctrl.vhd (revision 2) @@ -0,0 +1,199 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; + + +ENTITY st_ctrl IS + GENERIC ( + g_nof_mux : NATURAL := 1; + g_nof_stat : NATURAL := 512; + g_adr_w : NATURAL := 9; -- ceil_log2(g_nof_mux*g_nof_stat) + g_dly_rd : NATURAL := 1; + g_dly_mul : NATURAL := 4; + g_dly_acc : NATURAL := 2; + g_dly_out : NATURAL := 2 + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + + in_sync : IN STD_LOGIC; + in_val : IN STD_LOGIC; + + rd_en : OUT STD_LOGIC; + rd_adr : OUT STD_LOGIC_VECTOR(g_adr_w-1 DOWNTO 0); + rd_val : OUT STD_LOGIC; + + mult_val : OUT STD_LOGIC; + acc_load : OUT STD_LOGIC; + + wr_en : OUT STD_LOGIC; + wr_adr : OUT STD_LOGIC_VECTOR(g_adr_w-1 DOWNTO 0); + + out_val : OUT STD_LOGIC; + out_val_m : OUT STD_LOGIC_VECTOR(g_nof_mux-1 DOWNTO 0); + out_adr : OUT STD_LOGIC_VECTOR(g_adr_w-1 DOWNTO 0) + ); +END; + + +ARCHITECTURE rtl OF st_ctrl IS + + CONSTANT c_mux_w : NATURAL := true_log2(g_nof_mux); + + CONSTANT c_tin_mul : NATURAL := 0; + CONSTANT c_tot_mul : NATURAL := c_tin_mul + g_dly_mul; + + CONSTANT c_tin_acc : NATURAL := c_tot_mul; + CONSTANT c_tot_acc : NATURAL := c_tin_acc + g_dly_acc; + + CONSTANT c_tin_wr : NATURAL := c_tot_acc; + + CONSTANT c_tin_rd : NATURAL := c_tin_acc - g_dly_rd; + CONSTANT c_tot_rd : NATURAL := c_tin_acc; + + CONSTANT c_tin_out : NATURAL := c_tot_rd; + CONSTANT c_tot_out : NATURAL := c_tin_out + g_dly_out; + + SIGNAL dly_val : STD_LOGIC_VECTOR(0 TO c_tin_wr); + SIGNAL dly_sync : STD_LOGIC_VECTOR(0 TO c_tin_wr); + SIGNAL dly_load : STD_LOGIC_VECTOR(c_tin_rd TO c_tin_wr); + + SIGNAL i_rd_adr : STD_LOGIC_VECTOR(rd_adr'RANGE); + SIGNAL nxt_rd_adr : STD_LOGIC_VECTOR(rd_adr'RANGE); + + SIGNAL i_wr_adr : STD_LOGIC_VECTOR(wr_adr'RANGE); + SIGNAL nxt_wr_adr : STD_LOGIC_VECTOR(wr_adr'RANGE); + + SIGNAL i_out_adr : STD_LOGIC_VECTOR(out_adr'RANGE); + SIGNAL nxt_out_adr : STD_LOGIC_VECTOR(out_adr'RANGE); + + SIGNAL i_out_val : STD_LOGIC; + + SIGNAL nxt_load : STD_LOGIC; + +BEGIN + + -- hardwired + + dly_val (0) <= in_val; + dly_sync(0) <= in_sync; + + rd_en <= dly_val (c_tin_rd); + rd_val <= dly_val (c_tot_rd); + + mult_val <= dly_val(c_tin_acc); + acc_load <= dly_load(c_tin_acc) OR (NOT dly_val(c_tin_acc)); + + wr_en <= dly_val(c_tin_wr); + i_out_val <= dly_load(c_tot_out) AND dly_val(c_tot_out); + + rd_adr <= i_rd_adr; + wr_adr <= i_wr_adr; + out_adr <= i_out_adr; + out_val <= i_out_val; + + no_mux : IF g_nof_mux = 1 GENERATE + out_val_m <= (OTHERS => 'X'); + END GENERATE; + + gen_mux : IF g_nof_mux > 1 GENERATE + p_out_val_m: PROCESS (i_out_val, i_out_adr) + BEGIN + out_val_m <= (OTHERS => '0'); + FOR i IN 0 TO g_nof_mux-1 LOOP + IF UNSIGNED(i_out_adr(c_mux_w-1 DOWNTO 0)) = i THEN + out_val_m(i) <= i_out_val; + END IF; + END LOOP; + END PROCESS; + END GENERATE; + + -- registers + regs: PROCESS(rst,clk) + BEGIN + IF rst='1' THEN + i_rd_adr <= (OTHERS => '0'); + i_wr_adr <= (OTHERS => '0'); + i_out_adr <= (OTHERS => '0'); + dly_load <= (OTHERS => '1'); + dly_val (dly_val 'LOW+1 TO dly_val 'HIGH) <= (OTHERS => '0'); + dly_sync(dly_sync'LOW+1 TO dly_sync'HIGH) <= (OTHERS => '0'); + ELSIF rising_edge(clk) THEN + i_rd_adr <= nxt_rd_adr; + i_wr_adr <= nxt_wr_adr; + i_out_adr <= nxt_out_adr; + dly_load <= nxt_load & dly_load(dly_load'LOW TO dly_load'HIGH-1); + dly_val (dly_val 'LOW+1 TO dly_val 'HIGH) <= dly_val (dly_val 'LOW to dly_val 'HIGH-1); + dly_sync(dly_sync'LOW+1 TO dly_sync'HIGH) <= dly_sync (dly_sync'LOW to dly_sync'HIGH-1); + END IF; + END PROCESS; + + rd_ctrl: PROCESS(i_rd_adr, dly_load, dly_val, dly_sync) + BEGIN + nxt_load <= dly_load(dly_load'LOW); + nxt_rd_adr <= i_rd_adr; + IF dly_sync(c_tin_rd)='1' THEN + nxt_rd_adr <= (OTHERS => '0'); + nxt_load <= '1'; + ELSIF dly_val(c_tin_rd)='1' THEN + IF UNSIGNED(i_rd_adr)=g_nof_mux*g_nof_stat-1 THEN + nxt_rd_adr <= (OTHERS => '0'); + nxt_load <= '0'; + ELSE + nxt_rd_adr <= STD_LOGIC_VECTOR(UNSIGNED(i_rd_adr)+1); + END IF; + END IF; + END PROCESS; + + out_ctrl: PROCESS(i_out_adr, dly_val, dly_sync) + BEGIN + nxt_out_adr <= i_out_adr; + IF dly_sync(c_tot_out)='1' THEN + nxt_out_adr <= (OTHERS => '0'); + ELSIF dly_val(c_tot_out)='1' THEN + IF UNSIGNED(i_out_adr)=g_nof_mux*g_nof_stat-1 THEN + nxt_out_adr <= (OTHERS => '0'); + ELSE + nxt_out_adr <= STD_LOGIC_VECTOR(UNSIGNED(i_out_adr)+1); + END IF; + END IF; + END PROCESS; + + wr_ctrl: PROCESS(i_wr_adr,dly_val,dly_sync) + BEGIN + nxt_wr_adr <= i_wr_adr; + IF dly_sync(c_tin_wr)='1' THEN + nxt_wr_adr <= (OTHERS => '0'); + ELSIF dly_val(c_tin_wr)='1' THEN + IF UNSIGNED(i_wr_adr)=g_nof_mux*g_nof_stat-1 THEN + nxt_wr_adr <= (OTHERS => '0'); + ELSE + nxt_wr_adr <= STD_LOGIC_VECTOR(UNSIGNED(i_wr_adr)+1); + END IF; + END IF; + END PROCESS; + +END rtl;
st_ctrl.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: st_sst.vhd =================================================================== --- st_sst.vhd (nonexistent) +++ st_sst.vhd (revision 2) @@ -0,0 +1,318 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2011 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib, common_ram_lib, common_counter_lib, mm_lib, technology_lib, dp_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE mm_lib.common_field_pkg.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +-- Purpose: +-- Store the (auto)power statistics of a complex input stream with +-- blocks of nof_stat multiplexed subbands into a MM register. +-- Description: +-- +-- When the treshold register is set to 0 the statistics will be auto- +-- correlations. +-- In case the treshold register is set to a non-zero value, it allows +-- to create a sample & hold function for the a-input of the multiplier. +-- The a-input of the multiplier is updated every "treshold" clockcycle. +-- Thereby cross statistics can be created. +-- +-- After each sync the MM register gets updated with the (auto) power statistics +-- of the previous sync interval. The length of the sync interval determines +-- the nof accumlations per statistic, hence the integration time. See st_calc +-- for more details. +-- Remarks: +-- . The in_sync is assumed to be a pulse an interpreted directly. +-- . The MM register is single page RAM to save memory resources. Therefore +-- just after the sync its contents is undefined when it gets written, but +-- after that its contents remains stable for the rest of the sync interval. +-- Therefore it is not necessary to use a dual page register that swaps at +-- the sync. +-- . The minimum g_nof_stat = 8. Lower values lead to simulation errors. This is +-- due to the read latency of 2 of the accumulation memory in the st_calc entity. + +ENTITY st_sst IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_nof_stat : NATURAL := 512; -- nof accumulators + g_xst_enable : BOOLEAN := FALSE; -- when set to true, an extra memory is instantiated to hold the imaginary part of the cross-correlation results + g_in_data_w : NATURAL := 18; -- width o dth edata to be accumulated + g_stat_data_w : NATURAL := 54; -- statistics accumulator width + g_stat_data_sz : NATURAL := 2 -- statistics word width >= statistics accumulator width and fit in a power of 2 multiple 32b MM words + ); + PORT ( + mm_rst : IN STD_LOGIC; + mm_clk : IN STD_LOGIC; + dp_rst : IN STD_LOGIC; + dp_clk : IN STD_LOGIC; + + -- Streaming + in_complex : IN t_dp_sosi; -- Complex input data + + -- Memory Mapped + ram_st_sst_mosi : IN t_mem_mosi; + ram_st_sst_miso : OUT t_mem_miso; + reg_st_sst_mosi : IN t_mem_mosi := c_mem_mosi_rst; + reg_st_sst_miso : OUT t_mem_miso := c_mem_miso_rst + ); +END st_sst; + + +ARCHITECTURE str OF st_sst IS + + CONSTANT c_nof_stat_w : NATURAL := ceil_log2(g_nof_stat); + CONSTANT c_nof_word : NATURAL := g_stat_data_sz*g_nof_stat; + CONSTANT c_nof_word_w : NATURAL := ceil_log2(c_nof_word); + CONSTANT g_stat_word_w : NATURAL := g_stat_data_sz*c_word_w; + CONSTANT zeros : STD_LOGIC_VECTOR(c_nof_stat_w-1 DOWNTO 0) := (OTHERS => '0'); + + -- Statistics register + CONSTANT c_mm_ram : t_c_mem := (latency => 1, + adr_w => c_nof_word_w, + dat_w => c_word_w, + nof_dat => c_nof_word, + init_sl => '0'); -- MM side : sla_in, sla_out + CONSTANT c_stat_ram : t_c_mem := (latency => 1, + adr_w => c_nof_stat_w, + dat_w => g_stat_word_w, + nof_dat => g_nof_stat, + init_sl => '0'); -- ST side : stat_mosi + + CONSTANT c_field_arr : t_common_field_arr(0 DOWNTO 0) := (0=> ( field_name_pad("treshold"), "RW", c_nof_stat_w, field_default(0) )); + + SIGNAL mm_fields_out : STD_LOGIC_VECTOR(field_slv_out_len(c_field_arr)-1 DOWNTO 0); + SIGNAL treshold : STD_LOGIC_VECTOR(c_nof_stat_w-1 DOWNTO 0); + + TYPE reg_type IS RECORD + in_sosi_reg : t_dp_sosi; + in_a_re : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO 0); + in_a_im : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO 0); + END RECORD; + + SIGNAL r, rin : reg_type; + SIGNAL in_sync : STD_LOGIC; + SIGNAL stat_data_re : STD_LOGIC_VECTOR(g_stat_data_w-1 DOWNTO 0); + SIGNAL stat_data_im : STD_LOGIC_VECTOR(g_stat_data_w-1 DOWNTO 0); + + SIGNAL wrdata_re : STD_LOGIC_VECTOR(c_mem_data_w-1 DOWNTO 0); + SIGNAL wrdata_im : STD_LOGIC_VECTOR(c_mem_data_w-1 DOWNTO 0); + + SIGNAL stat_mosi : t_mem_mosi; + SIGNAL count : STD_LOGIC_VECTOR(c_nof_stat_w-1 DOWNTO 0); + + SIGNAL ram_st_sst_mosi_arr : t_mem_mosi_arr(c_nof_complex-1 DOWNTO 0) := (OTHERS => c_mem_mosi_rst); + SIGNAL ram_st_sst_miso_arr : t_mem_miso_arr(c_nof_complex-1 DOWNTO 0) := (OTHERS => c_mem_miso_rst); + +BEGIN + + ------------------------------------------------------------------------------ + -- Register map for the treshold register + ------------------------------------------------------------------------------ + register_map : ENTITY mm_lib.mm_fields + GENERIC MAP( + g_cross_clock_domain => TRUE, + g_field_arr => c_field_arr + ) + PORT MAP ( + mm_rst => mm_rst, + mm_clk => mm_clk, + + mm_mosi => reg_st_sst_mosi, + mm_miso => reg_st_sst_miso, + + slv_rst => dp_rst, + slv_clk => dp_clk, + + slv_out => mm_fields_out + ); + + treshold <= mm_fields_out(field_hi(c_field_arr, "treshold") DOWNTO field_lo(c_field_arr, "treshold")); + + ------------------------------------------------------------------------------ + -- Input registers and preparation of the input data for the multiplier. + ------------------------------------------------------------------------------ + comb : PROCESS(r, dp_rst, in_complex, count, treshold) + VARIABLE v : reg_type; + BEGIN + v := r; + v.in_sosi_reg := in_complex; + + IF(count = zeros OR treshold = zeros) THEN + v.in_a_re := in_complex.re(g_in_data_w-1 DOWNTO 0); + v.in_a_im := in_complex.im(g_in_data_w-1 DOWNTO 0); + END IF; + + IF(dp_rst = '1') THEN + v.in_a_re := (OTHERS => '0'); + v.in_a_im := (OTHERS => '0'); + END IF; + + rin <= v; + + END PROCESS comb; + + regs : PROCESS(dp_clk) + BEGIN + IF rising_edge(dp_clk) THEN + r <= rin; + END IF; + END PROCESS; + + ------------------------------------------------------------------------------ + -- Counter used to detect when treshold is reached in order to load new + -- input vlaues for the multiplier. + ------------------------------------------------------------------------------ + treshold_cnt : ENTITY common_counter_lib.common_counter + GENERIC MAP( + g_latency => 1, + g_init => 0, + g_width => c_nof_stat_w, + g_max => 0, + g_step_size => 1 + ) + PORT MAP ( + rst => dp_rst, + clk => dp_clk, + cnt_clr => in_complex.eop, + cnt_en => in_complex.valid, + cnt_max => treshold, + count => count + ); + + in_sync <= in_complex.sync; + + st_calc : ENTITY work.st_calc + GENERIC MAP ( + g_technology => g_technology, + g_nof_mux => 1, + g_nof_stat => g_nof_stat, + g_in_dat_w => g_in_data_w, + g_out_dat_w => g_stat_data_w, + g_out_adr_w => c_nof_stat_w, + g_complex => g_xst_enable + ) + PORT MAP ( + rst => dp_rst, + clk => dp_clk, + in_ar => r.in_a_re, + in_ai => r.in_a_im, + in_br => r.in_sosi_reg.re(g_in_data_w-1 DOWNTO 0), + in_bi => r.in_sosi_reg.im(g_in_data_w-1 DOWNTO 0), + in_val => r.in_sosi_reg.valid, + in_sync => in_sync, + out_adr => stat_mosi.address(c_stat_ram.adr_w-1 DOWNTO 0), + out_re => stat_data_re, + out_im => stat_data_im, + out_val => stat_mosi.wr, + out_val_m => OPEN + ); + + wrdata_re <= RESIZE_MEM_UDATA(stat_data_re); + wrdata_im <= RESIZE_MEM_UDATA(stat_data_im); + + stat_reg_re : ENTITY common_ram_lib.common_ram_crw_crw_ratio + GENERIC MAP ( + g_technology => g_technology, + g_ram_a => c_mm_ram, + g_ram_b => c_stat_ram, + g_init_file => "UNUSED" + ) + PORT MAP ( + rst_a => mm_rst, + clk_a => mm_clk, + + rst_b => dp_rst, + clk_b => dp_clk, + + wr_en_a => ram_st_sst_mosi_arr(0).wr, -- only for diagnostic purposes, typically statistics are read only + wr_dat_a => ram_st_sst_mosi_arr(0).wrdata(c_mm_ram.dat_w-1 DOWNTO 0), + adr_a => ram_st_sst_mosi_arr(0).address(c_mm_ram.adr_w-1 DOWNTO 0), + rd_en_a => ram_st_sst_mosi_arr(0).rd, + rd_dat_a => ram_st_sst_miso_arr(0).rddata(c_mm_ram.dat_w-1 DOWNTO 0), + rd_val_a => ram_st_sst_miso_arr(0).rdval, + + wr_en_b => stat_mosi.wr, + wr_dat_b => wrdata_re(c_stat_ram.dat_w-1 DOWNTO 0), + adr_b => stat_mosi.address(c_stat_ram.adr_w-1 DOWNTO 0), + rd_en_b => '0', + rd_dat_b => OPEN, + rd_val_b => OPEN + ); + + gen_re: IF g_xst_enable=FALSE GENERATE + ram_st_sst_mosi_arr(0) <= ram_st_sst_mosi; + ram_st_sst_miso <= ram_st_sst_miso_arr(0); + END GENERATE; + + gen_im: IF g_xst_enable=TRUE GENERATE + --------------------------------------------------------------- + -- COMBINE MEMORY MAPPED INTERFACES + --------------------------------------------------------------- + -- Combine the internal array of mm interfaces for both real + -- and imaginary part. + u_mem_mux_select : entity mm_lib.common_mem_mux + generic map ( + g_nof_mosi => c_nof_complex, + g_mult_addr_w => c_nof_word_w + ) + port map ( + mosi => ram_st_sst_mosi, + miso => ram_st_sst_miso, + mosi_arr => ram_st_sst_mosi_arr, + miso_arr => ram_st_sst_miso_arr + ); + + stat_reg_im : ENTITY common_ram_lib.common_ram_crw_crw_ratio + GENERIC MAP ( + g_technology => g_technology, + g_ram_a => c_mm_ram, + g_ram_b => c_stat_ram, + g_init_file => "UNUSED" + ) + PORT MAP ( + rst_a => mm_rst, + clk_a => mm_clk, + + rst_b => dp_rst, + clk_b => dp_clk, + + wr_en_a => ram_st_sst_mosi_arr(1).wr, -- only for diagnostic purposes, typically statistics are read only + wr_dat_a => ram_st_sst_mosi_arr(1).wrdata(c_mm_ram.dat_w-1 DOWNTO 0), + adr_a => ram_st_sst_mosi_arr(1).address(c_mm_ram.adr_w-1 DOWNTO 0), + rd_en_a => ram_st_sst_mosi_arr(1).rd, + rd_dat_a => ram_st_sst_miso_arr(1).rddata(c_mm_ram.dat_w-1 DOWNTO 0), + rd_val_a => ram_st_sst_miso_arr(1).rdval, + + wr_en_b => stat_mosi.wr, + wr_dat_b => wrdata_im(c_stat_ram.dat_w-1 DOWNTO 0), + adr_b => stat_mosi.address(c_stat_ram.adr_w-1 DOWNTO 0), + rd_en_b => '0', + rd_dat_b => OPEN, + rd_val_b => OPEN + ); + + END GENERATE; + +END str;
st_sst.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: tb_mmf_st_sst.vhd =================================================================== --- tb_mmf_st_sst.vhd (nonexistent) +++ tb_mmf_st_sst.vhd (revision 2) @@ -0,0 +1,236 @@ + +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2012 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- +-- +-- Purpose: Testbench for the st_sst unit. +-- To be used in conjunction with python script: ../python/tc_mmf_st_sst.py +-- +-- +-- Usage in non-auto-mode (c_modelsim_start = 0 in python): +-- > as 5 +-- > run -all +-- > Run python script in separate terminal: "python tc_mmf_st_xst.py --unb 0 --bn 0 --sim" +-- > Check the results of the python script. +-- > Stop the simulation manually in Modelsim by pressing the stop-button. +-- > Evalute the WAVE window. + +LIBRARY IEEE, common_pkg_lib, common_ram_lib, mm_lib, diag_lib, dp_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE common_pkg_lib.common_str_pkg.ALL; +USE common_pkg_lib.tb_common_pkg.ALL; +USE mm_lib.tb_common_mem_pkg.ALL; +USE mm_lib.mm_file_unb_pkg.ALL; +USE mm_lib.mm_file_pkg.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; +USE diag_lib.diag_pkg.ALL; + +ENTITY tb_mmf_st_sst IS + GENERIC( + g_nof_stat : NATURAL := 8; -- nof accumulators + g_xst_enable : BOOLEAN := TRUE; + g_in_data_w : NATURAL := 16; + g_stat_data_w : NATURAL := 56; -- statistics accumulator width + g_stat_data_sz : NATURAL := 2; -- statistics word width >= statistics accumulator width and fit in a power of 2 multiple 32b MM words + g_nof_instances : NATURAL := 4; -- The number of st_sst instances in parallel. + g_nof_frames : NATURAL := 1 + ); +END tb_mmf_st_sst; + +ARCHITECTURE tb OF tb_mmf_st_sst IS + + CONSTANT c_sim : BOOLEAN := TRUE; + + ---------------------------------------------------------------------------- + -- Clocks and resets + ---------------------------------------------------------------------------- + CONSTANT c_mm_clk_period : TIME := 100 ps; + CONSTANT c_dp_clk_period : TIME := 2 ns; + CONSTANT c_sclk_period : TIME := 1250 ps; + CONSTANT c_dp_pps_period : NATURAL := 64; + + SIGNAL dp_pps : STD_LOGIC; + + SIGNAL mm_rst : STD_LOGIC := '1'; + SIGNAL mm_clk : STD_LOGIC := '0'; + + SIGNAL dp_rst : STD_LOGIC; + SIGNAL dp_clk : STD_LOGIC := '0'; + + ---------------------------------------------------------------------------- + -- MM buses + ---------------------------------------------------------------------------- + SIGNAL reg_diag_bg_mosi : t_mem_mosi; + SIGNAL reg_diag_bg_miso : t_mem_miso; + + SIGNAL ram_diag_bg_mosi : t_mem_mosi; + SIGNAL ram_diag_bg_miso : t_mem_miso; + + SIGNAL ram_st_sst_mosi : t_mem_mosi; + SIGNAL ram_st_sst_miso : t_mem_miso; + + SIGNAL reg_st_sst_mosi : t_mem_mosi; + SIGNAL reg_st_sst_miso : t_mem_miso; + + SIGNAL ram_st_sst_mosi_arr : t_mem_mosi_arr(g_nof_instances-1 DOWNTO 0); + SIGNAL ram_st_sst_miso_arr : t_mem_miso_arr(g_nof_instances-1 DOWNTO 0); + + SIGNAL reg_st_sst_mosi_arr : t_mem_mosi_arr(g_nof_instances-1 DOWNTO 0); + SIGNAL reg_st_sst_miso_arr : t_mem_miso_arr(g_nof_instances-1 DOWNTO 0); + + -- Custom definitions of constants + CONSTANT c_bg_block_len : NATURAL := g_nof_stat*g_nof_frames; + CONSTANT c_complex_factor : NATURAL := sel_a_b(g_xst_enable, c_nof_complex, 1); + CONSTANT c_ram_addr_w : NATURAL := ceil_log2(g_stat_data_sz*g_nof_stat*c_complex_factor); + + -- Configuration of the block generator: + CONSTANT c_bg_nof_output_streams : POSITIVE := g_nof_instances; + CONSTANT c_bg_buf_dat_w : POSITIVE := c_nof_complex*g_in_data_w; + CONSTANT c_bg_buf_adr_w : POSITIVE := ceil_log2(c_bg_block_len); + CONSTANT c_bg_data_file_prefix : STRING := "UNUSED"; + CONSTANT c_bg_data_file_index_arr : t_nat_natural_arr := array_init(0, g_nof_instances, 1); + + -- Signal declarations to connect block generator to the DUT + SIGNAL bg_siso_arr : t_dp_siso_arr(c_bg_nof_output_streams-1 DOWNTO 0) := (OTHERS=>c_dp_siso_rdy); + SIGNAL bg_sosi_arr : t_dp_sosi_arr(c_bg_nof_output_streams-1 DOWNTO 0); + +BEGIN + + ---------------------------------------------------------------------------- + -- Clock and reset generation + ---------------------------------------------------------------------------- + mm_clk <= NOT mm_clk AFTER c_mm_clk_period/2; + mm_rst <= '1', '0' AFTER c_mm_clk_period*5; + + dp_clk <= NOT dp_clk AFTER c_dp_clk_period/2; + dp_rst <= '1', '0' AFTER c_dp_clk_period*5; + + ------------------------------------------------------------------------------ + -- External PPS + ------------------------------------------------------------------------------ + proc_common_gen_pulse(1, c_dp_pps_period, '1', dp_clk, dp_pps); + + ---------------------------------------------------------------------------- + -- Procedure that polls a sim control file that can be used to e.g. get + -- the simulation time in ns + ---------------------------------------------------------------------------- + mmf_poll_sim_ctrl_file(c_mmf_unb_file_path & "sim.ctrl", c_mmf_unb_file_path & "sim.stat"); + + ---------------------------------------------------------------------------- + -- MM buses + ---------------------------------------------------------------------------- + u_mm_file_reg_diag_bg : mm_file GENERIC MAP(mmf_unb_file_prefix(0, 0, "BN") & "REG_DIAG_BG") + PORT MAP(mm_rst, mm_clk, reg_diag_bg_mosi, reg_diag_bg_miso); + + u_mm_file_ram_diag_bg : mm_file GENERIC MAP(mmf_unb_file_prefix(0, 0, "BN") & "RAM_DIAG_BG") + PORT MAP(mm_rst, mm_clk, ram_diag_bg_mosi, ram_diag_bg_miso); + + u_mm_file_ram_st_sst : mm_file GENERIC MAP(mmf_unb_file_prefix(0, 0, "BN") & "RAM_ST_SST") + PORT MAP(mm_rst, mm_clk, ram_st_sst_mosi, ram_st_sst_miso); + + u_mm_file_reg_st_sst : mm_file GENERIC MAP(mmf_unb_file_prefix(0, 0, "BN") & "REG_ST_SST") + PORT MAP(mm_rst, mm_clk, reg_st_sst_mosi, reg_st_sst_miso); + + ---------------------------------------------------------------------------- + -- Source: block generator + ---------------------------------------------------------------------------- + u_bg : ENTITY diag_lib.mms_diag_block_gen + GENERIC MAP( + g_nof_streams => c_bg_nof_output_streams, + g_buf_dat_w => c_bg_buf_dat_w, + g_buf_addr_w => c_bg_buf_adr_w, + g_file_index_arr => c_bg_data_file_index_arr, + g_file_name_prefix => c_bg_data_file_prefix + ) + PORT MAP( + -- System + mm_rst => mm_rst, + mm_clk => mm_clk, + dp_rst => dp_rst, + dp_clk => dp_clk, + en_sync => dp_pps, + -- MM interface + reg_bg_ctrl_mosi => reg_diag_bg_mosi, + reg_bg_ctrl_miso => reg_diag_bg_miso, + ram_bg_data_mosi => ram_diag_bg_mosi, + ram_bg_data_miso => ram_diag_bg_miso, + -- ST interface + out_siso_arr => bg_siso_arr, + out_sosi_arr => bg_sosi_arr + ); + + -- Combine the internal array of mm interfaces for the beamlet statistics to one array that is connected to the port of bf + u_mem_mux_ram_sst : ENTITY mm_lib.common_mem_mux + GENERIC MAP ( + g_nof_mosi => g_nof_instances, + g_mult_addr_w => c_ram_addr_w + ) + PORT MAP ( + mosi => ram_st_sst_mosi, + miso => ram_st_sst_miso, + mosi_arr => ram_st_sst_mosi_arr, + miso_arr => ram_st_sst_miso_arr + ); + + u_mem_mux_reg_sst : ENTITY mm_lib.common_mem_mux + GENERIC MAP ( + g_nof_mosi => g_nof_instances, + g_mult_addr_w => 1 + ) + PORT MAP ( + mosi => reg_st_sst_mosi, + miso => reg_st_sst_miso, + mosi_arr => reg_st_sst_mosi_arr, + miso_arr => reg_st_sst_miso_arr + ); + + ---------------------------------------------------------------------------- + -- DUT: Device Under Test + ---------------------------------------------------------------------------- + gen_duts : FOR I IN 0 TO g_nof_instances-1 GENERATE + u_dut : ENTITY work.st_sst + GENERIC MAP( + g_nof_stat => g_nof_stat, + g_xst_enable => g_xst_enable, + g_in_data_w => g_in_data_w, + g_stat_data_w => g_stat_data_w, + g_stat_data_sz => g_stat_data_sz + ) + PORT MAP( + mm_rst => mm_rst, + mm_clk => mm_clk, + dp_rst => dp_rst, + dp_clk => dp_clk, + + -- Streaming + in_complex => bg_sosi_arr(I), + + -- Memory Mapped + ram_st_sst_mosi => ram_st_sst_mosi_arr(I), + ram_st_sst_miso => ram_st_sst_miso_arr(I), + reg_st_sst_mosi => reg_st_sst_mosi_arr(I), + reg_st_sst_miso => reg_st_sst_miso_arr(I) + ); + END GENERATE; + +END tb;
tb_mmf_st_sst.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: tb_st_acc.vhd =================================================================== --- tb_st_acc.vhd (nonexistent) +++ tb_st_acc.vhd (revision 2) @@ -0,0 +1,174 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +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; + + +ENTITY tb_st_acc IS + GENERIC ( + g_dat_w : NATURAL := 6; + g_acc_w : NATURAL := 9; + g_hold_load : BOOLEAN := TRUE; + g_pipeline_input : NATURAL := 0; + g_pipeline_output : NATURAL := 4 + ); +END tb_st_acc; + + +ARCHITECTURE tb OF tb_st_acc IS + + CONSTANT clk_period : TIME := 10 ns; + + CONSTANT c_pipeline : NATURAL := g_pipeline_input + g_pipeline_output; + + FUNCTION func_acc(in_dat, in_acc : STD_LOGIC_VECTOR; + in_val, in_load : STD_LOGIC) RETURN STD_LOGIC_VECTOR IS + VARIABLE v_dat, v_acc, v_result : INTEGER; + BEGIN + -- Calculate expected result + IF in_val='0' THEN -- hold: out_acc = in_acc + v_result := TO_SINT(in_acc); + ELSIF in_load='1' THEN -- force: out_acc = 0 + in_dat + v_result := TO_SINT(in_dat); + ELSE -- accumulate: out_acc = in_acc + in_dat + v_result := TO_SINT(in_dat) + TO_SINT(in_acc); + END IF; + -- Wrap to avoid warning: NUMERIC_STD.TO_SIGNED: vector truncated + IF v_result > 2**(g_acc_w-1)-1 THEN v_result := v_result - 2**g_acc_w; END IF; + IF v_result < -2**(g_acc_w-1) THEN v_result := v_result + 2**g_acc_w; END IF; + RETURN TO_SVEC(v_result, g_acc_w); + END; + + SIGNAL tb_end : STD_LOGIC := '0'; + SIGNAL clk : STD_LOGIC := '0'; + + SIGNAL in_dat : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + SIGNAL in_acc : STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0) := (OTHERS=>'0'); + SIGNAL in_val : STD_LOGIC; + SIGNAL in_load : STD_LOGIC; + SIGNAL out_val : STD_LOGIC; + SIGNAL out_acc : STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0); + + SIGNAL expected_acc_p : STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0); + SIGNAL expected_acc : STD_LOGIC_VECTOR(g_acc_w-1 DOWNTO 0); + +BEGIN + + clk <= NOT clk OR tb_end AFTER clk_period/2; + + ------------------------------------------------------------------------------ + -- Input stimuli + ------------------------------------------------------------------------------ + + -- run -all + p_stimuli : PROCESS + BEGIN + in_load <= '0'; + in_dat <= TO_SVEC(0, g_dat_w); + in_val <= '0'; + WAIT UNTIL rising_edge(clk); + FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(clk); END LOOP; + + in_load <= '1'; + in_val <= '1'; + FOR R IN 0 TO 2 LOOP -- Repeat some intervals marked by in_load = '1' + in_load <= '1'; + -- All combinations + FOR I IN -2**(g_dat_w-1) TO 2**(g_dat_w-1)-1 LOOP + in_dat <= TO_SVEC(I, g_dat_w); + WAIT UNTIL rising_edge(clk); + -- keep in_load low during rest of period + in_load <= '0'; +-- -- keep in_val low during rest of st_acc latency, to ease manual interpretation of out_acc as in_acc +-- in_val <= '0'; +-- FOR J IN 1 TO c_pipeline-1 LOOP WAIT UNTIL rising_edge(clk); END LOOP; +-- in_val <= '1'; + END LOOP; + END LOOP; + in_load <= '1'; -- keep '1' to avoid further toggling of out_acc (in a real design this would safe power) + in_val <= '0'; + FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(clk); END LOOP; + tb_end <= '1'; + WAIT; + END PROCESS; + + + ------------------------------------------------------------------------------ + -- DUT + ------------------------------------------------------------------------------ + + dut : ENTITY work.st_acc + GENERIC MAP ( + g_dat_w => g_dat_w, + g_acc_w => g_acc_w, + g_hold_load => g_hold_load, + g_pipeline_input => g_pipeline_input, + g_pipeline_output => g_pipeline_output + ) + PORT MAP ( + clk => clk, + clken => '1', + in_load => in_load, -- start of accumulate period + in_dat => in_dat, + in_acc => in_acc, -- use only one accumulator + in_val => in_val, + out_acc => out_acc, + out_val => out_val + ); + + in_acc <= out_acc WHEN c_pipeline>0 ELSE + out_acc WHEN rising_edge(clk); -- if DUT has no pipeline, then register feedback to avoid combinatorial loop + + + ------------------------------------------------------------------------------ + -- Verify + ------------------------------------------------------------------------------ + + expected_acc <= func_acc(in_dat, in_acc, in_val, in_load); + + u_result : ENTITY common_components_lib.common_pipeline + GENERIC MAP ( + g_representation => "SIGNED", + g_pipeline => c_pipeline, + g_reset_value => 0, + g_in_dat_w => g_acc_w, + g_out_dat_w => g_acc_w + ) + PORT MAP ( + clk => clk, + clken => '1', + in_dat => expected_acc, + out_dat => expected_acc_p + ); + + p_verify : PROCESS(clk) + BEGIN + IF rising_edge(clk) THEN + IF out_val='1' THEN + ASSERT out_acc = expected_acc_p REPORT "Error: wrong result" SEVERITY ERROR; + END IF; + END IF; + END PROCESS; + +END tb;
tb_st_acc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: tb_st_calc.vhd =================================================================== --- tb_st_calc.vhd (nonexistent) +++ tb_st_calc.vhd (revision 2) @@ -0,0 +1,130 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; + + +ENTITY tb_st_calc IS + GENERIC ( + g_in_dat_w : NATURAL := 16; + g_out_dat_w : NATURAL := 32 + ); +END tb_st_calc; + + +ARCHITECTURE tb OF tb_st_calc IS + + CONSTANT clk_period : TIME := 10 ns; + + CONSTANT c_nof_sync : NATURAL := 3; + CONSTANT c_nof_stat : NATURAL := 100; + CONSTANT c_out_adr_w : NATURAL := ceil_log2(c_nof_stat); + CONSTANT c_gap_size : NATURAL := 2**c_out_adr_w - c_nof_stat; + + CONSTANT c_nof_accum_per_sync : NATURAL := 5; -- integration time + + SIGNAL tb_end : STD_LOGIC := '0'; + SIGNAL clk : STD_LOGIC := '0'; + SIGNAL rst : STD_LOGIC; + + SIGNAL in_sync : STD_LOGIC; + SIGNAL in_val : STD_LOGIC; + SIGNAL in_dat : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + + SIGNAL in_a_re : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + SIGNAL in_a_im : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + SIGNAL in_b_re : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + SIGNAL in_b_im : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + + SIGNAL out_adr : STD_LOGIC_VECTOR(c_out_adr_w-1 DOWNTO 0); + SIGNAL out_re : STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); + SIGNAL out_im : STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); + SIGNAL out_val : STD_LOGIC; + +BEGIN + + clk <= NOT clk OR tb_end AFTER clk_period/2; + + in_a_re <= in_dat; + in_a_im <= in_dat; + in_b_re <= in_dat; + in_b_im <= in_dat; + + in_dat <= (OTHERS=>'0') WHEN rst='1' ELSE INCR_UVEC(in_dat, 1) WHEN rising_edge(clk) AND in_val='1'; + + -- run 1 us + p_stimuli : PROCESS + BEGIN + rst <= '1'; + in_sync <= '0'; + in_val <= '0'; + 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; + + FOR I IN 0 TO c_nof_sync-1 LOOP + in_sync <= '1'; + WAIT UNTIL rising_edge(clk); + in_sync <= '0'; + + FOR J IN 0 TO c_nof_accum_per_sync-1 LOOP + in_val <= '1'; + FOR I IN 0 TO c_nof_stat-1 LOOP WAIT UNTIL rising_edge(clk); END LOOP; + in_val <= '0'; + FOR I IN 0 TO c_gap_size-1 LOOP WAIT UNTIL rising_edge(clk); END LOOP; + END LOOP; + END LOOP; + FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(clk); END LOOP; + tb_end <= '1'; + WAIT; + END PROCESS; + + u_dut : ENTITY work.st_calc + GENERIC MAP ( + g_nof_mux => 1, + g_nof_stat => c_nof_stat, + g_in_dat_w => g_in_dat_w, + g_out_dat_w => g_out_dat_w, + g_out_adr_w => c_out_adr_w, + g_complex => FALSE + ) + PORT MAP ( + rst => rst, + clk => clk, + clken => '1', + in_ar => in_a_re, + in_ai => in_a_im, + in_br => in_b_re, + in_bi => in_b_im, + in_val => in_val, + in_sync => in_sync, + out_adr => out_adr, + out_re => out_re, + out_im => out_im, + out_val => out_val, + out_val_m => OPEN + ); + +END tb;
tb_st_calc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property

powered by: WebSVN 2.1.0

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