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

Subversion Repositories astron_filter

Compare Revisions

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

Rev 1 → Rev 2

/trunk/fil_pkg.vhd
0,0 → 1,68
-------------------------------------------------------------------------------
-- Author: Harm Jan Pepping : pepping at astron.nl: 2012
-- Copyright (C) 2012
-- 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;
 
package fil_pkg is
 
-- Parameters for the (wideband) poly phase filter.
type t_fil_ppf is record
wb_factor : natural; -- = 1, the wideband factor
nof_chan : natural; -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan
nof_bands : natural; -- = 1024, the number of polyphase channels (= number of points of the FFT)
nof_taps : natural; -- = 16, the number of FIR taps per subband
nof_streams : natural; -- = 1, the number of streams that are served by the same coefficients.
backoff_w : natural; -- = 0, number of bits for input backoff to avoid output overflow
in_dat_w : natural; -- = 8, number of input bits per stream
out_dat_w : natural; -- = 16, number of output bits per stream
coef_dat_w : natural; -- = 16, data width of the FIR coefficients
end record;
constant c_fil_ppf : t_fil_ppf := (1, 0, 1024, 16, 1, 0, 8, 16, 16);
-- Definitions for fil slv array (an array can not have unconstraint elements, so choose sufficiently wide 32 bit slv elements)
subtype t_fil_slv_arr is t_slv_32_arr; -- use subtype to ease interfacing to existing types and to have central definition for filter components
constant c_fil_slv_w : natural := 32; -- match slv width of t_fil_slv_arr
-- Record with the pipeline settings for the filter units.
type t_fil_ppf_pipeline is record
-- generic for the taps and coefficients memory
mem_delay : natural; -- = 1
-- generics for the multiplier in in the filter unit
mult_input : natural; -- = 1
mult_product : natural; -- = 1
mult_output : natural; -- = 1
-- generics for the adder tree in in the filter unit
adder_stage : natural; -- = 1
-- generics for the requantizer in the filter unit
requant_remove_lsb : natural; -- = 1
requant_remove_msb : natural; -- = 0
end record;
constant c_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
end package fil_pkg;
 
package body fil_pkg is
end fil_pkg;
 
/trunk/fil_ppf_ctrl.vhd
0,0 → 1,156
-------------------------------------------------------------------------------
--
-- 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/>.
--
-------------------------------------------------------------------------------
-- Purpose: Controlling the data streams for the filter units
--
-- Description: This unit prepairs the data streams for the ppf_filter
-- unit. Incoming data (in_dat) is combined with stored
-- data (taps_in_vec) to generate a new vector that is
-- offered to the filter unit: taps_out_vec.
--
-- It also delays the in_val signal in order to generate
-- the out_val that is proper alligned with the output data
-- that is coming from the filter unit.
--
 
library IEEE, common_pkg_lib;
use IEEE.std_logic_1164.ALL;
use IEEE.numeric_std.ALL;
use common_pkg_lib.common_pkg.ALL;
use work.fil_pkg.ALL;
 
entity fil_ppf_ctrl is
generic (
g_fil_ppf : t_fil_ppf;
g_fil_ppf_pipeline : t_fil_ppf_pipeline
);
port (
rst : in std_logic := '0';
clk : in std_logic;
in_dat : in std_logic_vector;
in_val : in std_logic;
taps_in_vec : in std_logic_vector;
taps_rdaddr : out std_logic_vector;
taps_wraddr : out std_logic_vector;
taps_wren : out std_logic;
taps_out_vec: out std_logic_vector;
out_val : out std_logic
);
end fil_ppf_ctrl;
 
architecture rtl of fil_ppf_ctrl is
type t_in_dat_delay is array (g_fil_ppf_pipeline.mem_delay downto 0) of std_logic_vector(g_fil_ppf.in_dat_w*g_fil_ppf.nof_streams-1 downto 0);
constant c_addr_w : natural := ceil_log2(g_fil_ppf.nof_bands * (2**g_fil_ppf.nof_chan));
constant c_ctrl_latency : natural := 1; -- due to taps_out_vec register
constant c_mult_latency : natural := g_fil_ppf_pipeline.mult_input + g_fil_ppf_pipeline.mult_product + g_fil_ppf_pipeline.mult_output;
constant c_adder_latency : natural := ceil_log2(g_fil_ppf.nof_taps) * g_fil_ppf_pipeline.adder_stage;
constant c_filter_zdly : natural := g_fil_ppf.nof_bands * (2**g_fil_ppf.nof_chan);
 
constant c_tot_latency : natural := g_fil_ppf_pipeline.mem_delay + c_ctrl_latency + c_mult_latency +
c_adder_latency + g_fil_ppf_pipeline.requant_remove_lsb +
g_fil_ppf_pipeline.requant_remove_msb;
constant c_single_taps_vec_w : natural := g_fil_ppf.in_dat_w*g_fil_ppf.nof_taps;
constant c_taps_vec_w : natural := c_single_taps_vec_w*g_fil_ppf.nof_streams;
type reg_type is record
in_dat_arr : t_in_dat_delay; -- Input register for the data
init_dly_cnt : integer range 0 to c_filter_zdly; -- Counter used to overcome the settling time of the filter.
val_dly : std_logic_vector(c_tot_latency-1 downto 0); -- Delay register for the valid signal
rd_addr : std_logic_vector(c_addr_w-1 downto 0); -- The read address
wr_addr : std_logic_vector(c_addr_w-1 downto 0); -- The write address
wr_en : std_logic; -- Write enable signal for the taps memory
taps_out_vec : std_logic_vector(c_taps_vec_w-1 downto 0); -- Output register containing the next taps data
out_val_ena : std_logic; -- Output enable
end record;
signal r, rin : reg_type;
begin
comb : process(r, rst, in_val, in_dat, taps_in_vec)
variable v : reg_type;
begin
 
v := r;
v.wr_en := '0';
-- Perform the shifting for the shiftregister for the valid signal and the input data:
v.val_dly(0) := in_val;
v.val_dly(c_tot_latency-1 downto 1) := r.val_dly(c_tot_latency-2 downto 0);
v.in_dat_arr(0) := RESIZE_SVEC(in_dat, r.in_dat_arr(0)'LENGTH);
v.in_dat_arr(g_fil_ppf_pipeline.mem_delay downto 1) := r.in_dat_arr(g_fil_ppf_pipeline.mem_delay-1 downto 0);
if(r.val_dly(0) = '1') then -- Wait for incoming data
v.rd_addr := INCR_UVEC(r.rd_addr, 1);
end if;
 
if(r.val_dly(c_tot_latency-2) = '1') then -- Wait for incoming data
if(r.init_dly_cnt < c_filter_zdly) then
v.init_dly_cnt := r.init_dly_cnt + 1;
v.out_val_ena := '0';
else
v.out_val_ena := '1';
end if;
end if;
if(r.val_dly(g_fil_ppf_pipeline.mem_delay+1) = '1') then
v.wr_addr := INCR_UVEC(r.wr_addr, 1);
end if;
 
if(r.val_dly(g_fil_ppf_pipeline.mem_delay) = '1') then
for I in 0 to g_fil_ppf.nof_streams-1 loop
v.taps_out_vec((I+1)*c_single_taps_vec_w-1 downto I*c_single_taps_vec_w) := taps_in_vec((I+1)*c_single_taps_vec_w - g_fil_ppf.in_dat_w -1 downto I*c_single_taps_vec_w) & r.in_dat_arr(g_fil_ppf_pipeline.mem_delay)((I+1)*g_fil_ppf.in_dat_w-1 downto I*g_fil_ppf.in_dat_w);
end loop;
--v.taps_out_vec := taps_in_vec(taps_in_vec'HIGH - g_fil_ppf.in_dat_w downto 0) & r.in_dat_arr(g_fil_ppf_pipeline.mem_delay);
v.wr_en := '1';
end if;
if(rst = '1') then
v.init_dly_cnt := 0;
v.in_dat_arr := (others => (others => '0'));
v.val_dly := (others => '0');
v.rd_addr := (others => '0');
v.wr_addr := (others => '0');
v.wr_en := '0';
v.taps_out_vec := (others => '0');
v.out_val_ena := '0';
end if;
rin <= v;
end process comb;
regs : process(clk)
begin
if rising_edge(clk) then
r <= rin;
end if;
end process;
taps_rdaddr <= r.rd_addr;
taps_wraddr <= r.wr_addr;
taps_wren <= r.wr_en;
taps_out_vec <= r.taps_out_vec;
out_val <= r.val_dly(c_tot_latency-1) AND r.out_val_ena;
end rtl;
/trunk/fil_ppf_filter.vhd
0,0 → 1,144
-------------------------------------------------------------------------------
--
-- Copyright (C) 2012
-- 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/>.
--
-------------------------------------------------------------------------------
-- Purpose: A FIR filter implementation.
--
-- Description: This unit instantiates a multiplier for every tap.
-- All output of the mutipliers are added using an
-- adder-tree structure.
--
-- Remarks: .
--
 
library IEEE, common_pkg_lib, astron_multiplier_lib, astron_requantize_lib, astron_adder_lib;
use IEEE.std_logic_1164.ALL;
use IEEE.numeric_std.ALL;
--USE technology_lib.technology_select_pkg.ALL;
use common_pkg_lib.common_pkg.ALL;
use work.fil_pkg.ALL;
 
entity fil_ppf_filter is
generic (
g_technology : NATURAL := 0;
g_fil_ppf : t_fil_ppf;
g_fil_ppf_pipeline : t_fil_ppf_pipeline
);
port (
clk : in std_logic;
rst : in std_logic;
taps : in std_logic_vector;
coefs : in std_logic_vector;
result : out std_logic_vector
);
end fil_ppf_filter;
 
architecture rtl of fil_ppf_filter is
 
constant c_in_dat_w : natural := g_fil_ppf.backoff_w + g_fil_ppf.in_dat_w; -- add optional input backoff to fit output overshoot
constant c_prod_w : natural := c_in_dat_w + g_fil_ppf.coef_dat_w - c_sign_w; -- skip double sign bit
constant c_gain_w : natural := 0; -- no need for adder bit growth so fixed 0, because filter coefficients should have DC gain <= 1.
-- The adder tree bit growth depends on DC gain of FIR coefficients, not on ceil_log2(g_fil_ppf.nof_taps).
constant c_sum_w : natural := c_prod_w + c_gain_w;
constant c_ppf_lsb_w : natural := c_sum_w - g_fil_ppf.out_dat_w;
signal prod_vec : std_logic_vector(g_fil_ppf.nof_taps*c_prod_w-1 downto 0);
signal adder_out : std_logic_vector(c_sum_w-1 downto 0) := (others => '0');
signal requant_out : std_logic_vector(g_fil_ppf.out_dat_w-1 downto 0);
signal in_taps : std_logic_vector(g_fil_ppf.in_dat_w*g_fil_ppf.nof_taps-1 downto 0); -- taps input data as stored in RAM
signal in_taps_backoff : std_logic_vector( c_in_dat_w*g_fil_ppf.nof_taps-1 downto 0); -- taps input data with backoff as use in FIR
begin
in_taps <= taps; -- Use this help signal to create a 'HIGH downto 0 vector again.
---------------------------------------------------------------
-- GENERATE THE MUTIPLIERS
---------------------------------------------------------------
-- For every tap a unique multiplier is instantiated that
-- multiplies the data tap with the corresponding filter coefficient
gen_multipliers : for I in 0 to g_fil_ppf.nof_taps-1 generate
in_taps_backoff((I+1)*c_in_dat_w-1 downto I*c_in_dat_w) <= resize_svec(in_taps((I+1)*g_fil_ppf.in_dat_w-1 downto I*g_fil_ppf.in_dat_w), c_in_dat_w);
u_multiplier : entity astron_multiplier_lib.common_mult
generic map (
g_technology => g_technology,
g_variant => "IP",
g_in_a_w => c_in_dat_w,
g_in_b_w => g_fil_ppf.coef_dat_w,
g_out_p_w => c_prod_w,
g_nof_mult => 1,
g_pipeline_input => g_fil_ppf_pipeline.mult_input,
g_pipeline_product => g_fil_ppf_pipeline.mult_product,
g_pipeline_output => g_fil_ppf_pipeline.mult_output,
g_representation => "SIGNED"
)
port map (
rst => rst,
clk => clk,
clken => '1',
in_a => in_taps_backoff((I+1)*c_in_dat_w-1 downto I*c_in_dat_w),
in_b => coefs((I+1)*g_fil_ppf.coef_dat_w-1 downto I*g_fil_ppf.coef_dat_w),
out_p => prod_vec((I+1)*c_prod_w-1 downto I*c_prod_w)
);
end generate;
 
---------------------------------------------------------------
-- ADDER TREE
---------------------------------------------------------------
-- The adder tree summarizes the outputs of all multipliers.
u_adder_tree : entity astron_adder_lib.common_adder_tree(str)
generic map (
g_representation => "SIGNED",
g_pipeline => g_fil_ppf_pipeline.adder_stage,
g_nof_inputs => g_fil_ppf.nof_taps,
g_dat_w => c_prod_w,
g_sum_w => c_sum_w
)
port map (
clk => clk,
in_dat => prod_vec,
sum => adder_out
);
u_requantize_addeer_output : entity astron_requantize_lib.common_requantize
generic map (
g_representation => "SIGNED",
g_lsb_w => c_ppf_lsb_w,
g_lsb_round => TRUE,
g_lsb_round_clip => FALSE,
g_msb_clip => FALSE,
g_msb_clip_symmetric => FALSE,
g_pipeline_remove_lsb => g_fil_ppf_pipeline.requant_remove_lsb,
g_pipeline_remove_msb => g_fil_ppf_pipeline.requant_remove_msb,
g_in_dat_w => c_sum_w,
g_out_dat_w => g_fil_ppf.out_dat_w
)
port map (
clk => clk,
clken => '1',
in_dat => adder_out,
out_dat => requant_out,
out_ovr => open
);
result <= RESIZE_SVEC(requant_out, result'LENGTH);
 
end rtl;
 
/trunk/fil_ppf_single.vhd
0,0 → 1,248
-------------------------------------------------------------------------------
--
-- Copyright (C) 2012
-- 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/>.
--
-------------------------------------------------------------------------------
-- Purpose: Performing a poly phase prefilter (PPF) function on one or multiple datastreams.
--
-- Description:
-- The poly phase prefilter (PPF) function is based on a taps memory, a
-- coefficients memory, a filter and a control unit.
--
-- The control unit writes the incoming data to the taps memory, along with
-- the historical tap data. It also drives the read addresses for both the
-- taps- and the coefficients memory. The output of the taps memory and the
-- coefficients memory are connected to the input of the filter unit that
-- peforms the actual filter function(multiply and accumulate). The prefilter
-- support multiple streams that share the same filter coefficients. The
-- filter coefficients can be written and read via the MM interface.
--
-- The PPF introduces a data valid latency of 1 tap, so nof_bands samples.
-- The nof_bands = nof_points of the FFT that gets the PPF output.
--
-- The following example shows the working for the poly phase prefilter
-- where nof_bands=4 and nof_taps=2. The total number of coefficients is 8.
-- For the given input stream all the multiplications and additions are
-- given that are required to generate the given output stream. Note that
-- every input sample is used nof_taps=2 times.
--
-- Time: t0 t1 ....
-- Incoming datastream: a0 a1 a2 a3 b0 b1 b2 b3 c0 c1 c2 c3 ....
-- Outgoing datastream: A0 A1 A2 A3 B0 B1 B2 B3 C0 C1 C2 C3 ....
--
-- A0 = coef0*a0 + coef1*b0
-- A1 = coef2*a1 + coef3*b1
-- A2 = coef4*a2 + coef5*b2
-- A3 = coef6*a3 + coef7*b3
--
-- B0 = coef0*b0 + coef1*c0
-- B1 = coef2*b1 + coef3*c1
-- B2 = coef4*b2 + coef5*c2
-- B3 = coef6*b3 + coef7*c3
--
-- C0 = coef0*c0 + coef1*d0
-- C1 = coef2*c1 + coef3*d1
-- C2 = coef4*c2 + coef5*d2
-- C3 = coef6*c3 + coef7*d3
--
-- Remarks:
-- . See also description tb_fil_ppf_single.vhd for more info.
--
library IEEE, common_pkg_lib, astron_ram_lib, astron_mm_lib;
use IEEE.std_logic_1164.ALL;
use IEEE.numeric_std.ALL;
use common_pkg_lib.common_pkg.ALL;
use astron_ram_lib.common_ram_pkg.ALL;
use work.fil_pkg.ALL;
 
entity fil_ppf_single is
generic (
g_fil_ppf : t_fil_ppf := c_fil_ppf;
g_fil_ppf_pipeline : t_fil_ppf_pipeline := c_fil_ppf_pipeline;
g_file_index_arr : t_nat_natural_arr := array_init(0, 128, 1); -- default use the instance index as file index 0, 1, 2, 3, 4 ...
g_coefs_file_prefix : string := "hex/coef" -- Relative path to the mif files that contain the initial data for the coefficients memories
); -- The sequence number and ".mif"-extension are added within the entity.
port (
dp_clk : in std_logic;
dp_rst : in std_logic;
mm_clk : in std_logic;
mm_rst : in std_logic;
ram_coefs_mosi : in t_mem_mosi;
ram_coefs_miso : out t_mem_miso := c_mem_miso_rst;
in_dat : in std_logic_vector(g_fil_ppf.nof_streams*g_fil_ppf.in_dat_w-1 downto 0);
in_val : in std_logic;
out_dat : out std_logic_vector(g_fil_ppf.nof_streams*g_fil_ppf.out_dat_w-1 downto 0);
out_val : out std_logic
);
end fil_ppf_single;
 
architecture rtl of fil_ppf_single is
constant c_coefs_postfix : string := ".mif";
constant c_taps_mem_addr_w : natural := ceil_log2(g_fil_ppf.nof_bands * (2**g_fil_ppf.nof_chan));
constant c_coef_mem_addr_w : natural := ceil_log2(g_fil_ppf.nof_bands);
constant c_taps_mem_delay : natural := g_fil_ppf_pipeline.mem_delay;
constant c_coef_mem_delay : natural := g_fil_ppf_pipeline.mem_delay;
constant c_taps_mem_data_w : natural := g_fil_ppf.in_dat_w*g_fil_ppf.nof_taps;
constant c_coef_mem_data_w : natural := g_fil_ppf.coef_dat_w;
 
constant c_taps_mem : t_c_mem := (latency => c_taps_mem_delay,
adr_w => c_taps_mem_addr_w,
dat_w => c_taps_mem_data_w,
nof_dat => g_fil_ppf.nof_bands * (2**g_fil_ppf.nof_chan),
init_sl => '0'); -- use '0' instead of 'X' to avoid RTL RAM simulation warnings due to read before write
 
constant c_coef_mem : t_c_mem := (latency => c_coef_mem_delay,
adr_w => c_coef_mem_addr_w,
dat_w => c_coef_mem_data_w,
nof_dat => g_fil_ppf.nof_bands,
init_sl => '0'); -- use '0' instead of 'X' to avoid RTL RAM simulation warnings due to read before write
 
signal ram_coefs_mosi_arr : t_mem_mosi_arr(g_fil_ppf.nof_taps-1 downto 0);
signal ram_coefs_miso_arr : t_mem_miso_arr(g_fil_ppf.nof_taps-1 downto 0) := (others => c_mem_miso_rst);
signal taps_wren : std_logic;
signal taps_rdaddr : std_logic_vector(c_taps_mem_addr_w-1 downto 0);
signal taps_wraddr : std_logic_vector(c_taps_mem_addr_w-1 downto 0);
signal taps_mem_out_vec : std_logic_vector(c_taps_mem_data_w*g_fil_ppf.nof_streams-1 downto 0);
signal taps_mem_in_vec : std_logic_vector(c_taps_mem_data_w*g_fil_ppf.nof_streams-1 downto 0);
signal coef_rdaddr : std_logic_vector(c_coef_mem_addr_w-1 downto 0);
signal coef_vec : std_logic_vector(c_coef_mem_data_w*g_fil_ppf.nof_taps-1 downto 0);
begin
 
---------------------------------------------------------------
-- MEMORY FOR THE HISTORICAL TAP DATA
---------------------------------------------------------------
gen_taps_mems : for I in 0 to g_fil_ppf.nof_streams-1 generate
u_taps_mem : entity astron_ram_lib.common_ram_r_w
generic map (
g_ram => c_taps_mem,
g_init_file => "UNUSED" -- assume block RAM gets initialized to '0' by default in simulation
)
port map (
rst => dp_rst,
clk => dp_clk,
wr_en => taps_wren,
wr_adr => taps_wraddr,
wr_dat => taps_mem_in_vec((I+1)*c_taps_mem_data_w-1 downto I*c_taps_mem_data_w),
rd_en => '1',
rd_adr => taps_rdaddr,
rd_dat => taps_mem_out_vec((I+1)*c_taps_mem_data_w-1 downto I*c_taps_mem_data_w),
rd_val => open
);
end generate;
---------------------------------------------------------------
-- COMBINE MEMORY MAPPED INTERFACES
---------------------------------------------------------------
-- Combine the internal array of mm interfaces for the coefficents
-- memory to one array that is connected to the port of the fil_ppf
u_mem_mux_coef : entity astron_mm_lib.common_mem_mux
generic map (
g_nof_mosi => g_fil_ppf.nof_taps,
g_mult_addr_w => c_coef_mem_addr_w
)
port map (
mosi => ram_coefs_mosi,
miso => ram_coefs_miso,
mosi_arr => ram_coefs_mosi_arr,
miso_arr => ram_coefs_miso_arr
);
 
---------------------------------------------------------------
-- GENERATE THE COEFFICIENT MEMORIES
---------------------------------------------------------------
-- For every tap a unique memory is instantiated that holds
-- the corresponding coefficients for all the bands.
gen_coef_mems : for I in 0 to g_fil_ppf.nof_taps-1 generate
u_coef_mem : entity astron_ram_lib.common_ram_crw_crw
generic map (
g_ram => c_coef_mem,
-- Sequence number and ".hex" extensie are added to the relative path in case a ram file is provided.
g_init_file => sel_a_b(g_coefs_file_prefix = "UNUSED", g_coefs_file_prefix, g_coefs_file_prefix & "_" & NATURAL'IMAGE(g_file_index_arr(I)) & c_coefs_postfix)
)
port map (
-- MM side
rst_a => mm_rst,
clk_a => mm_clk,
wr_en_a => ram_coefs_mosi_arr(I).wr,
wr_dat_a => ram_coefs_mosi_arr(I).wrdata(g_fil_ppf.coef_dat_w-1 downto 0),
adr_a => ram_coefs_mosi_arr(I).address(c_coef_mem.adr_w-1 downto 0),
rd_en_a => ram_coefs_mosi_arr(I).rd,
rd_dat_a => ram_coefs_miso_arr(I).rddata(g_fil_ppf.coef_dat_w-1 downto 0),
rd_val_a => ram_coefs_miso_arr(I).rdval,
-- Datapath side
rst_b => dp_rst,
clk_b => dp_clk,
wr_en_b => '0',
wr_dat_b => (others =>'0'),
adr_b => coef_rdaddr,
rd_en_b => '1',
rd_dat_b => coef_vec((I+1)*c_coef_mem_data_w-1 downto I*c_coef_mem_data_w),
rd_val_b => open
);
end generate;
-- Address the coefficients, taking into account the nof_chan. The coefficients will only be
-- updated if all 2**nof_chan time-multiples signals are processed.
coef_rdaddr <= taps_rdaddr(c_taps_mem_addr_w-1 downto (c_taps_mem_addr_w - c_coef_mem_addr_w));
 
---------------------------------------------------------------
-- FILTER CONTROL UNIT
---------------------------------------------------------------
-- The control unit receives the input data and writes it to
-- the tap memory, along with the historical tap data.
-- It also controls the reading of the coefficients memory.
u_fil_ctrl : entity work.fil_ppf_ctrl
generic map (
g_fil_ppf_pipeline => g_fil_ppf_pipeline,
g_fil_ppf => g_fil_ppf
)
port map (
clk => dp_clk,
rst => dp_rst,
in_dat => in_dat,
in_val => in_val,
taps_rdaddr => taps_rdaddr,
taps_wraddr => taps_wraddr,
taps_wren => taps_wren,
taps_in_vec => taps_mem_out_vec,
taps_out_vec => taps_mem_in_vec,
out_val => out_val
);
 
---------------------------------------------------------------
-- FILTER UNIT
---------------------------------------------------------------
-- The actual filter unit that performs the filter operations:
-- multiplications and additions.
gen_filter_units : for I in 0 to g_fil_ppf.nof_streams-1 generate
u_filter : entity work.fil_ppf_filter
generic map (
g_fil_ppf_pipeline => g_fil_ppf_pipeline,
g_fil_ppf => g_fil_ppf
)
port map (
clk => dp_clk,
rst => dp_rst,
taps => taps_mem_out_vec((I+1)*c_taps_mem_data_w-1 downto I*c_taps_mem_data_w),
coefs => coef_vec,
result => out_dat((I+1)*g_fil_ppf.out_dat_w-1 downto I*g_fil_ppf.out_dat_w)
);
end generate;
end rtl;
/trunk/fil_ppf_wide.vhd
0,0 → 1,272
-------------------------------------------------------------------------------
--
-- Copyright (C) 2012
-- 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/>.
--
-------------------------------------------------------------------------------
-- Purpose: Performing a poly phase prefilter (PPF) function on one or more
-- wideband data stream.
--
-- Description:
-- The poly phase prefilter function is applied on multiple inputs. In
-- array notation:
--
-- parallel serial type
-- in_dat_arr [wb_factor][nof_streams] [t][nof_channels] int
-- out_dat_arr [wb_factor][nof_streams] [t][nof_channels] int
--
-- If g_big_endian_wb_*=true then the time t to wb_factor P mapping for the
-- fil_ppf_wide is t[0,1,2,3] = P[3,2,1,0], else when it is false then the
-- mapping is t[3,2,1,0] = P[3,2,1,0]. The mapping can be selected
-- independently for the in_dat_arr and the out_dat_arr.
--
-- The incoming data must be divided over the inputs as shown in the
-- following example for nof_streams=1 and wb_factor is 4. The array
-- index I runs from [wb_factor*nof_streams-1:0].
--
-- array wb stream time index when g_big_endian_wb_*=true)
-- index index index
-- I P S t
-- 3 3 0 : 0, 4, 8, 12, 16, ...
-- 2 2 0 : 1, 5, 9, 13, 17, ...
-- 1 1 0 : 2, 6, 10, 14, 18, ...
-- 0 0 0 : 3, 7, 11, 15, 19, ...
-- ^
-- big endian
--
-- Every array input will be filtered by a fil_ppf_single instance. It is
-- also possible to offer multiple wideband input streams. Those wide
-- band input streams will share the filter coefficients. For a system with
-- nof_streams=2 and wb_factor=4 the array inputs become:
--
-- array wb stream time index when g_big_endian_wb_*=true)
-- index index index
-- I P S t
-- 7 3 1 : 0, 4, 8, 12, 16, ...
-- 6 3 0 : 0, 4, 8, 12, 16, ...
-- 5 2 1 : 1, 5, 9, 13, 17, ...
-- 4 2 0 : 1, 5, 9, 13, 17, ...
-- 3 1 1 : 2, 6, 10, 14, 18, ...
-- 2 1 0 : 2, 6, 10, 14, 18, ...
-- 1 0 1 : 3, 7, 11, 15, 19, ...
-- 0 0 0 : 3, 7, 11, 15, 19, ...
-- ^
-- big endian
--
-- Note that I, P and S all increment in the same direction and t increments
-- in the opposite direction of P. This is the g_big_endian_wb_in=true and
-- g_big_endian_wb_out=true format for the in_dat_arr and out_dat_arr.
--
-- If g_big_endian_wb_in=false and g_big_endian_wb_out=false for little endian
-- format, then the time t increments in the same direction as P, for both
-- in_dat_arr and out_dat_arr, so then I, P and S all increment in the same
-- direction:
--
-- array wb stream time index when g_big_endian_wb_*=false
-- index index index
-- I P S t
-- 7 3 1 : 3, 7, 11, 15, 19, ...
-- 6 3 0 : 3, 7, 11, 15, 19, ...
-- 5 2 1 : 2, 6, 10, 14, 18, ...
-- 4 2 0 : 2, 6, 10, 14, 18, ...
-- 3 1 1 : 1, 5, 9, 13, 17, ...
-- 2 1 0 : 1, 5, 9, 13, 17, ...
-- 1 0 1 : 0, 4, 8, 12, 16, ...
-- 0 0 0 : 0, 4, 8, 12, 16, ...
-- ^
-- little endian
--
-- The FIR coefficients must always be provided as for little endian wb input,
-- independent of g_big_endian_wb_in, because internally this fil_ppf_wide
-- adjusts the streams_in_arr to little endian wb input when needed.
--
-- With wb_factor > 1 and nof_streams > 1 the streams in in_dat_arr and
-- out_dat_arr are looped first and then the wb_factor is looped. This
-- fits with the fact that all streams for a certain wb_index use the same
-- filter coeffcients and may thus ease routing. The alternative would be
-- to group the data per stream and loop over the wb_factor first and then
-- over these wide band streams. This may ease the routing of the further
-- data processing per wide band stream. One may instante one fil_ppf_wide
-- for all streams (all using the same set of coefficients) or multiple
-- fil_ppf_wide instances for all streams (each with their own set of
-- coefficients).
--
-- Remarks:
-- . See also description tb_fil_ppf_single.vhd for more info.
--
library IEEE, common_pkg_lib, astron_ram_lib, astron_mm_lib;
use IEEE.std_logic_1164.ALL;
use IEEE.numeric_std.ALL;
use common_pkg_lib.common_pkg.ALL;
use astron_ram_lib.common_ram_pkg.ALL;
use work.fil_pkg.ALL;
 
entity fil_ppf_wide is
generic (
g_big_endian_wb_in : boolean := false;
g_big_endian_wb_out : boolean := false;
g_fil_ppf : t_fil_ppf := c_fil_ppf;
g_fil_ppf_pipeline : t_fil_ppf_pipeline := c_fil_ppf_pipeline;
g_coefs_file_prefix : string := "../../data/coef" -- Relative path to the mif files that contain the FIR the coefficients
-- The sequence number and ".mif"-extension are added within the entity.
);
port (
dp_clk : in std_logic;
dp_rst : in std_logic;
mm_clk : in std_logic;
mm_rst : in std_logic;
ram_coefs_mosi : in t_mem_mosi;
ram_coefs_miso : out t_mem_miso := c_mem_miso_rst;
in_dat_arr : in t_fil_slv_arr(g_fil_ppf.wb_factor*g_fil_ppf.nof_streams-1 downto 0); -- = t_slv_32_arr fits g_fil_ppf.in_dat_w <= 32
in_val : in std_logic;
out_dat_arr : out t_fil_slv_arr(g_fil_ppf.wb_factor*g_fil_ppf.nof_streams-1 downto 0); -- = t_slv_32_arr fits g_fil_ppf.out_dat_w <= 32
out_val : out std_logic
);
end fil_ppf_wide;
 
architecture rtl of fil_ppf_wide is
 
constant c_nof_mif_files : natural := g_fil_ppf.wb_factor * g_fil_ppf.nof_taps;
constant c_file_index_arr : t_nat_natural_arr := array_init(0, c_nof_mif_files, 1); -- use the instance index as file index 0, 1, 2, 3, 4 ...
type t_fil_ppf_arr is array(integer range <> ) of t_fil_ppf; -- An array of t_fil_ppf's generics.
type t_nat_natural_arr2 is array(integer range <> ) of t_nat_natural_arr(g_fil_ppf.nof_taps-1 downto 0); -- An array of arrays, used to point to the right .mif files for the coefficients
 
type t_streams_in_arr is array(integer range <> ) of std_logic_vector(g_fil_ppf.nof_streams*g_fil_ppf.in_dat_w -1 downto 0);
type t_streams_out_arr is array(integer range <> ) of std_logic_vector(g_fil_ppf.nof_streams*g_fil_ppf.out_dat_w -1 downto 0);
----------------------------------------------------------
-- This function creates an array of t_fil_ppf generics
-- for the single channel poly phase filters that are
-- used to compose the multichannel(wideband) poly phase
-- filter. The array is based on the content of the g_fil_ppf
-- generic that belongs to the fil_ppf_w entity.
-- Only the nof_bands is modified.
----------------------------------------------------------
function func_create_generics_for_ppfs(input: t_fil_ppf) return t_fil_ppf_arr is
variable v_nof_bands : natural := input.nof_bands/input.wb_factor; -- The nof_bands for the single channel poly phase filters
variable v_return : t_fil_ppf_arr(input.wb_factor-1 downto 0) := (others => input); -- Variable that holds the return values
begin
for P in 0 to input.wb_factor-1 loop
v_return(P).nof_bands := v_nof_bands; -- The new number of bands
end loop;
return v_return;
end;
----------------------------------------------------------
-- Function that divides the input file index array into
-- "wb_factor" new file index arrays.
----------------------------------------------------------
function func_create_file_index_array(input: t_nat_natural_arr; wb_factor: natural; nof_taps: natural) return t_nat_natural_arr2 is
variable v_return : t_nat_natural_arr2(wb_factor-1 downto 0); -- Variable that holds the return values
begin
for P in 0 to wb_factor-1 loop
for T in 0 to nof_taps-1 loop
v_return(P)(T) := input(P*nof_taps+T);
end loop;
end loop;
return v_return;
end;
constant c_fil_ppf_arr : t_fil_ppf_arr(g_fil_ppf.wb_factor-1 downto 0) := func_create_generics_for_ppfs(g_fil_ppf);
constant c_file_index_arr2 : t_nat_natural_arr2(g_fil_ppf.wb_factor-1 downto 0) := func_create_file_index_array(c_file_index_arr, g_fil_ppf.wb_factor, g_fil_ppf.nof_taps);
constant c_mem_addr_w : natural := ceil_log2(g_fil_ppf.nof_bands * g_fil_ppf.nof_taps / g_fil_ppf.wb_factor);
 
signal ram_coefs_mosi_arr : t_mem_mosi_arr(g_fil_ppf.wb_factor-1 downto 0);
signal ram_coefs_miso_arr : t_mem_miso_arr(g_fil_ppf.wb_factor-1 downto 0) := (others => c_mem_miso_rst);
 
signal streams_in_arr : t_streams_in_arr( g_fil_ppf.wb_factor-1 downto 0);
signal streams_out_arr : t_streams_out_arr(g_fil_ppf.wb_factor-1 downto 0);
signal streams_out_val_arr : std_logic_vector( g_fil_ppf.wb_factor-1 downto 0);
begin
---------------------------------------------------------------
-- COMBINE MEMORY MAPPED INTERFACES
---------------------------------------------------------------
-- Combine the internal array of mm interfaces for the coefficents
-- memory to one array that is connected to the port of the fil_ppf_w
u_mem_mux_coef : entity astron_mm_lib.common_mem_mux
generic map (
g_nof_mosi => g_fil_ppf.wb_factor,
g_mult_addr_w => c_mem_addr_w
)
port map (
mosi => ram_coefs_mosi,
miso => ram_coefs_miso,
mosi_arr => ram_coefs_mosi_arr,
miso_arr => ram_coefs_miso_arr
);
 
p_wire_input : process(in_dat_arr)
variable vP : natural;
begin
for P in 0 to g_fil_ppf.wb_factor-1 loop
if g_big_endian_wb_in=true then
vP := g_fil_ppf.wb_factor-1-P; -- convert input big endian time [0,1,2,3] to P [3,2,1,0] index mapping to internal little endian
else
vP := P; -- keep input little endian time [0,1,2,3] to P [0,1,2,3] index mapping
end if;
for S in 0 to g_fil_ppf.nof_streams-1 loop
streams_in_arr(vP)((S+1)*g_fil_ppf.in_dat_w-1 downto S*g_fil_ppf.in_dat_w) <= in_dat_arr(P*g_fil_ppf.nof_streams+S)(g_fil_ppf.in_dat_w-1 downto 0);
end loop;
end loop;
end process;
 
---------------------------------------------------------------
-- INSTANTIATE MULTIPLE SINGLE CHANNEL POLY PHASE FILTERS
---------------------------------------------------------------
gen_fil_ppf_singles : for P in 0 to g_fil_ppf.wb_factor-1 generate
u_fil_ppf_single : entity work.fil_ppf_single
generic map (
g_fil_ppf => c_fil_ppf_arr(P),
g_fil_ppf_pipeline => g_fil_ppf_pipeline,
g_file_index_arr => c_file_index_arr2(P), -- use (g_fil_ppf.wb_factor-1 - P) to try impact of reversed WB FIR coefficients
g_coefs_file_prefix => g_coefs_file_prefix
)
port map (
dp_clk => dp_clk,
dp_rst => dp_rst,
mm_clk => mm_clk,
mm_rst => mm_rst,
ram_coefs_mosi => ram_coefs_mosi_arr(P),
ram_coefs_miso => ram_coefs_miso_arr(P),
in_dat => streams_in_arr(P),
in_val => in_val,
out_dat => streams_out_arr(P),
out_val => streams_out_val_arr(P)
);
end generate;
p_wire_output : process(streams_out_arr)
variable vP : natural;
begin
for P in 0 to g_fil_ppf.wb_factor-1 loop
if g_big_endian_wb_out=true then
vP := g_fil_ppf.wb_factor-1-P; -- convert internal little endian to output big endian time [0,1,2,3] to P [3,2,1,0] index mapping
else
vP := P; -- keep internal little endian for output little endian time [0,1,2,3] to P [0,1,2,3] index mapping
end if;
for S in 0 to g_fil_ppf.nof_streams-1 loop
out_dat_arr(vP*g_fil_ppf.nof_streams+S) <= RESIZE_SVEC_32(streams_out_arr(P)((S+1)*g_fil_ppf.out_dat_w-1 downto S*g_fil_ppf.out_dat_w));
end loop;
end loop;
end process;
out_val <= streams_out_val_arr(0);
end rtl;
/trunk/hdllib.cfg
0,0 → 1,34
hdl_lib_name = astron_filter
hdl_library_clause_name = astron_filter_lib
hdl_lib_uses_synth = common_pkg astron_adder astron_multiplier astron_requantize dp_pkg astron_diagnostics astron_ram astron_mm astron_sim_tools
hdl_lib_uses_sim =
hdl_lib_technology =
 
synth_files =
fil_pkg.vhd
fil_ppf_ctrl.vhd
fil_ppf_filter.vhd
fil_ppf_single.vhd
fil_ppf_wide.vhd
test_bench_files =
tb_fil_ppf_single.vhd
tb_fil_ppf_wide.vhd
tb_fil_ppf_wide_file_data.vhd
tb_tb_fil_ppf_single.vhd
tb_tb_fil_ppf_wide.vhd
tb_tb_fil_ppf_wide_file_data.vhd
 
regression_test_vhdl =
tb_tb_fil_ppf_single.vhd
tb_tb_fil_ppf_wide.vhd
tb_tb_fil_ppf_wide_file_data.vhd
 
[modelsim_project_file]
modelsim_copy_files =
hex hex
data data
 
 
[quartus_project_file]
 
/trunk/tb_fil_ppf_single.vhd
0,0 → 1,437
-- Author: Harm Jan Pepping : hajee at astron.nl : April 2012
-- Eric Kooistra : kooistra at astron.nl: july 2016
--------------------------------------------------------------------------------
--
-- Copyright (C) 2012
-- 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/>.
--
--------------------------------------------------------------------------------
 
--
-- Purpose: Test bench for fil_ppf_single.vhd
--
-- The DUT fil_ppf_single.vhd has wb_factor = 1 fixed. For wb_factor > 1 use
-- the tb of fil_ppf_wide.vhd.
--
-- The testbench reads the filter coefficients from the reference dat file
-- and verifies that these are the same as the coeff in the corresponding
-- set of mif files (p_verify_ref_coeff_versus_mif_files) and as read via
-- MM from the coeff memories (p_verify_ref_coeff_versus_mm_ram).
--
-- The testbench inserts an pulse during the first nof_bands. The output is
-- verified by checking if the output values equal the filter coefficients
-- (p_verify_output). The coefficients appear in the order of the taps, but
-- in reversed order per tap.
--
-- The fil_ppf_filter in fil_ppf_single multiplies the in_dat by the filter
-- coefficients. The product has a double sign bit, whereby one sign bit is
-- dropped, because it only is needed to represent the positive result of
-- the product of the most negative in_dat and coeff, which does never occur
-- (because the most negative value is not used in the coefficients).
-- Therefore the product has width prod_w = in_dat_w + coef_dat_w - 1.
-- The fil_ppf_single assumes that the coefficients have DC gain = 1, so the
-- nof_taps and adder tree do not cause bit growth, thus sum_w = prod_w.
-- Therefore the maximum out_dat_w = sum_w. If out_dat_w is less, then the
-- sum_w - out_dat_w = lsb_w LSbits are rounded in fil_ppf_filter. This tb
-- compensates for the LSbits by scaling the input pulse such that the
-- out_dat still contains the exact coefficient values. Therefore in this tb
-- out_dat_w must be >= coef_dat_w (and then lsb_w <= in_dat_w-1).
--
-- The filter can operate on one or more streams in parallel. These streams
-- all share the same coefficient memory. The same pulse is applied to each
-- input stream in in_dat[nof_streams*in_dat_w-1:0] and verified for each
-- output stream in out_dat[nof_streams*out_dat_w-1:0] (p_verify_output).
--
-- Via g_enable_in_val_gaps it is possible toggle in_val in a random way to
-- verify that the DUT can handle arbitray gaps in in_dat.
--
-- It is possible to vary wb_factor, nof_chan, nof_bands, nof_taps, coef_w
-- and nof_streams. The input dat file is different for nof_taps, nof_bands
-- and coef_w. In addition the MIF files are different for wb_factor.
-- The nof_chan and nof_streams do not affect the input and output files,
-- because all multiplexed channels and pallellel streams use the same
-- filter coefficients.
--
-- The reference dat file is generated by the Matlab program:
--
-- $RADIOHDL_WORK/applications/apertif/matlab/run_pfir_coeff.m
--
-- The MIF files are generated by the Python script:
--
-- $RADIOHDL_WORK/libraries/dsp/filter/src/python/fil_ppf_create_mifs.py
--
-- The reference dat file and the MIF files use the same g_coefs_file_prefix.
-- For the reference dat file this prefix is expanded by nof_taps, nof_bands
-- and coef_dat_w and the MIF files in addition also have the wb_factor and
-- the MIF file index.
--
-- The example below shows how the mif file index relates to the reference
-- coefficients:
--
-- <g_coefs_file_prefix>_2taps_8bands_16b.dat
-- <g_coefs_file_prefix>_2taps_8bands_16b_4wb_0.mif
-- <g_coefs_file_prefix>_2taps_8bands_16b_4wb_1.mif
-- <g_coefs_file_prefix>_2taps_8bands_16b_4wb_2.mif
-- <g_coefs_file_prefix>_2taps_8bands_16b_4wb_3.mif
-- <g_coefs_file_prefix>_2taps_8bands_16b_4wb_4.mif
-- <g_coefs_file_prefix>_2taps_8bands_16b_4wb_5.mif
-- <g_coefs_file_prefix>_2taps_8bands_16b_4wb_6.mif
-- <g_coefs_file_prefix>_2taps_8bands_16b_4wb_7.mif
--
-- nof_taps = 2
-- nof_points = 8
-- pfir coef reference : 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15
-- pfir coef flip per tap : 7 6 5 4 3 2 1 0 15 14 13 12 11 10 9 8
--
--
-- wb_factor = 1: 7 6 5 4 3 2 1 0 15 14 13 12 11 10 9 8
--
-- time sample:
-- t0 t1 t2 t3 t4 t5 t6 t7t8 t9 t10t11t12t13t14t15
--
-- mif index:
-- 0 1
--
-- wb_index:
-- wb_factor = 4: 0: 7 3 15 11
-- 1: 6 2 14 10
-- 2: 5 1 13 9
-- 3: 4 0 12 8
--
-- time sample:
-- 0: t0 t4 t8 t12 MSpart
-- 1: t1 t5 t9 t13
-- 2: t2 t6 t10 t14
-- 3: t3 t7 t11 t15 LSpart
--
-- mif index:
-- 0: 0 1 first count taps
-- 1: 2 3 then count wb
-- 2: 4 5
-- 3: 6 7
--
-- Usage:
-- > run -all
-- > observe out_dat in analogue format in Wave window
-- > testbench is selftesting.
--
library ieee, common_pkg_lib, dp_pkg_lib, astron_diagnostics_lib, astron_ram_lib, astron_mm_lib;
use IEEE.std_logic_1164.all;
use IEEE.numeric_std.all;
use IEEE.std_logic_textio.all;
use STD.textio.all;
use common_pkg_lib.common_pkg.all;
use astron_ram_lib.common_ram_pkg.ALL;
use common_pkg_lib.common_lfsr_sequences_pkg.ALL;
use common_pkg_lib.tb_common_pkg.all;
use astron_mm_lib.tb_common_mem_pkg.ALL;
use dp_pkg_lib.dp_stream_pkg.ALL;
use work.fil_pkg.all;
 
entity tb_fil_ppf_single is
generic(
g_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
-- type t_fil_pipeline is record
-- -- generic for the taps and coefficients memory
-- mem_delay : natural; -- = 2
-- -- generics for the multiplier in in the filter unit
-- mult_input : natural; -- = 1
-- mult_product : natural; -- = 1
-- mult_output : natural; -- = 1
-- -- generics for the adder tree in in the filter unit
-- adder_stage : natural; -- = 1
-- -- generics for the requantizer in the filter unit
-- requant_remove_lsb : natural; -- = 1
-- requant_remove_msb : natural; -- = 0
-- end record;
g_fil_ppf : t_fil_ppf := (1, 1, 64, 8, 1, 0, 8, 16, 16);
-- type t_fil_ppf is record
-- wb_factor : natural; -- = 1, the wideband factor
-- nof_chan : natural; -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan
-- nof_bands : natural; -- = 128, the number of polyphase channels (= number of points of the FFT)
-- nof_taps : natural; -- = 16, the number of FIR taps per subband
-- nof_streams : natural; -- = 1, the number of streams that are served by the same coefficients.
-- backoff_w : natural; -- = 0, number of bits for input backoff to avoid output overflow
-- in_dat_w : natural; -- = 8, number of input bits per stream
-- out_dat_w : natural; -- = 23, number of output bits (per stream). It is set to in_dat_w+coef_dat_w-1 = 23 to be sure the requantizer
-- does not remove any of the data in order to be able to verify with the original coefficients values.
-- coef_dat_w : natural; -- = 16, data width of the FIR coefficients
-- end record;
g_coefs_file_prefix : string := "hex/run_pfir_coeff_m_incrementing";
g_enable_in_val_gaps : boolean := FALSE
);
end entity tb_fil_ppf_single;
 
architecture tb of tb_fil_ppf_single is
 
constant c_clk_period : time := 10 ns;
 
constant c_nof_channels : natural := 2**g_fil_ppf.nof_chan;
constant c_nof_coefs : natural := g_fil_ppf.nof_taps * g_fil_ppf.nof_bands; -- nof PFIR coef
constant c_nof_data_in_filter : natural := c_nof_coefs * c_nof_channels; -- nof PFIR coef expanded for all channels
constant c_nof_data_per_tap : natural := g_fil_ppf.nof_bands * c_nof_channels;
constant c_nof_bands_per_mif : natural := g_fil_ppf.nof_bands;
constant c_nof_mif_files : natural := g_fil_ppf.nof_taps;
constant c_mif_coef_mem_addr_w : natural := ceil_log2(g_fil_ppf.nof_bands);
constant c_mif_coef_mem_span : natural := 2**c_mif_coef_mem_addr_w; -- mif coef mem span for one tap
constant c_coefs_file_prefix : string := g_coefs_file_prefix & "_" & integer'image(g_fil_ppf.nof_taps) & "taps" &
"_" & integer'image(g_fil_ppf.nof_bands) & "points" &
"_" & integer'image(g_fil_ppf.coef_dat_w) & "b";
constant c_mif_file_prefix : string := c_coefs_file_prefix & "_" & "1wb";
constant c_mif_file_index_arr : t_nat_natural_arr := array_init(0, c_nof_mif_files, 1);
constant c_fil_prod_w : natural := g_fil_ppf.in_dat_w + g_fil_ppf.coef_dat_w - 1; -- skip double sign bit
constant c_fil_sum_w : natural := c_fil_prod_w; -- DC gain = 1
constant c_fil_lsb_w : natural := c_fil_sum_w - g_fil_ppf.out_dat_w; -- nof LSbits that get rounded for out_dat
constant c_in_ampl : natural := 2**c_fil_lsb_w; -- scale in_dat to compensate for rounding
 
constant c_gap_factor : natural := sel_a_b(g_enable_in_val_gaps, 3, 1);
-- input/output data width
constant c_in_dat_w : natural := g_fil_ppf.in_dat_w;
constant c_out_dat_w : natural := g_fil_ppf.out_dat_w; -- must be >= coef_dat_w to be able to show the coeff in out_dat
 
-- signal definitions
signal tb_end : std_logic := '0';
signal tb_end_mm : std_logic := '0';
signal tb_end_almost : std_logic := '0';
signal clk : std_logic := '0';
signal rst : std_logic := '0';
signal random : std_logic_vector(15 DOWNTO 0) := (OTHERS=>'0'); -- use different lengths to have different random sequences
 
signal ram_coefs_mosi : t_mem_mosi := c_mem_mosi_rst;
signal ram_coefs_miso : t_mem_miso;
 
signal in_dat : std_logic_vector(g_fil_ppf.nof_streams*c_in_dat_w-1 downto 0);
signal in_val : std_logic;
signal in_val_cnt : natural := 0;
signal in_gap : std_logic := '0';
 
signal out_dat : std_logic_vector(g_fil_ppf.nof_streams*c_out_dat_w-1 downto 0);
signal out_val : std_logic;
signal out_val_cnt : natural := 0;
 
signal mif_coefs_arr : t_integer_arr(g_fil_ppf.nof_bands-1 downto 0) := (OTHERS=>0); -- = PFIR coef for 1 tap as read from 1 MIF file
signal mif_dat_arr : t_integer_arr(c_nof_data_in_filter-1 downto 0) := (OTHERS=>0); -- = PFIR coef for all taps as read from all MIF files and expanded for all channels
 
signal ref_coefs_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0); -- = PFIR coef for all taps as read from the coefs file
signal ref_dat_arr : t_integer_arr(c_nof_data_in_filter-1 downto 0) := (OTHERS=>0); -- = PFIR coef for all taps as read from the coefs file expanded for all channels
signal ref_dat : integer := 0;
 
signal read_coefs_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0); -- = PFIR coef for all taps as read via MM from the coefs memories
 
begin
 
clk <= (not clk) or tb_end after c_clk_period/2;
rst <= '1', '0' after c_clk_period*7;
random <= func_common_random(random) WHEN rising_edge(clk);
in_gap <= random(random'HIGH) WHEN g_enable_in_val_gaps=TRUE ELSE '0';
 
---------------------------------------------------------------
-- SEND PULSE TO THE DATA INPUT
---------------------------------------------------------------
p_send_impulse : PROCESS
BEGIN
tb_end <= '0';
in_dat <= (OTHERS=>'0');
in_val <= '0';
proc_common_wait_until_low(clk, rst); -- Wait until reset has finished
proc_common_wait_some_cycles(clk, 10); -- Wait an additional amount of cycles
 
-- Pulse during first tap of all channels
FOR I IN 0 TO c_nof_data_per_tap-1 LOOP
FOR S IN 0 To g_fil_ppf.nof_streams-1 LOOP
in_dat((S+1)*c_in_dat_w-1 DOWNTO S*c_in_dat_w) <= TO_UVEC(c_in_ampl, c_in_dat_w);
END LOOP;
in_val <= '1';
proc_common_wait_some_cycles(clk, 1);
IF in_gap='1' THEN
in_val <= '0';
proc_common_wait_some_cycles(clk, 1);
END IF;
END LOOP;
 
-- Zero during next nof_taps-1 blocks, +1 more to account for block latency of PPF and +1 more to have zeros output in last block
in_dat <= (OTHERS=>'0');
FOR J IN 0 TO g_fil_ppf.nof_taps-2 +1 +1 LOOP
FOR I IN 0 TO c_nof_data_per_tap-1 LOOP
in_val <= '1';
proc_common_wait_some_cycles(clk, 1);
IF in_gap='1' THEN
in_val <= '0';
proc_common_wait_some_cycles(clk, 1);
END IF;
END LOOP;
END LOOP;
in_val <= '0';
 
-- Wait until done
proc_common_wait_some_cycles(clk, c_gap_factor*c_nof_data_per_tap); -- PPF latency of 1 tap
proc_common_wait_until_high(clk, tb_end_mm); -- MM read done
tb_end_almost <= '1';
proc_common_wait_some_cycles(clk, 10);
tb_end <= '1';
WAIT;
END PROCESS;
 
---------------------------------------------------------------
-- CREATE REFERENCE ARRAY
---------------------------------------------------------------
p_create_ref_from_coefs_file : PROCESS
variable v_coefs_flip_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0);
begin
-- Read all coeffs from coefs file
proc_common_read_integer_file(c_coefs_file_prefix & ".dat", 0, c_nof_coefs, 1, ref_coefs_arr);
wait for 1 ns;
-- Reverse the coeffs per tap
for J in 0 to g_fil_ppf.nof_taps-1 loop
for I in 0 to g_fil_ppf.nof_bands-1 loop
v_coefs_flip_arr(J*g_fil_ppf.nof_bands + g_fil_ppf.nof_bands-1-I) := ref_coefs_arr(J*g_fil_ppf.nof_bands+I);
end loop;
end loop;
-- Expand the channels (for one stream)
for I in 0 to c_nof_coefs-1 loop
for K in 0 to c_nof_channels-1 loop
ref_dat_arr(I*c_nof_channels + K) <= TO_SINT(TO_SVEC(v_coefs_flip_arr(I), g_fil_ppf.coef_dat_w));
end loop;
end loop;
wait;
end process;
 
p_create_ref_from_mif_file : PROCESS
begin
for J in 0 to g_fil_ppf.nof_taps-1 loop
-- Read coeffs per tap from MIF file
proc_common_read_mif_file(c_mif_file_prefix & "_" & integer'image(J) & ".mif", mif_coefs_arr);
wait for 1 ns;
-- Expand the channels (for one stream)
for I in 0 to g_fil_ppf.nof_bands-1 loop
for K in 0 to c_nof_channels-1 loop
mif_dat_arr(J*c_nof_data_per_tap + I*c_nof_channels + K) <= TO_SINT(TO_SVEC(mif_coefs_arr(I), g_fil_ppf.coef_dat_w));
end loop;
end loop;
end loop;
wait;
end process;
 
p_coefs_memory_read : process
variable v_mif_base : natural;
variable v_coef_offset : natural;
variable v_coef_index : natural;
begin
ram_coefs_mosi <= c_mem_mosi_rst;
for J in 0 to g_fil_ppf.nof_taps-1 loop
v_mif_base := J*c_mif_coef_mem_span;
v_coef_offset := g_fil_ppf.nof_bands*(J+1)-1;
for I in 0 to c_nof_bands_per_mif-1 loop
proc_mem_mm_bus_rd(v_mif_base+I, clk, ram_coefs_miso, ram_coefs_mosi);
proc_mem_mm_bus_rd_latency(1, clk);
v_coef_index := v_coef_offset - I;
read_coefs_arr(v_coef_index) <= TO_SINT(ram_coefs_miso.rddata(g_fil_ppf.coef_dat_w-1 DOWNTO 0));
end loop;
end loop;
proc_common_wait_some_cycles(clk, 1);
tb_end_mm <= '1';
wait;
end process;
 
p_verify_ref_coeff_versus_mif_files : PROCESS
begin
-- Wait until the coeff dat file and coeff MIF files have been read
proc_common_wait_until_low(clk, rst);
assert mif_dat_arr = ref_dat_arr report "Coefs file does not match coefs MIF files" severity error;
wait;
end process;
 
p_verify_ref_coeff_versus_mm_ram : PROCESS
begin
-- Wait until the coeff dat file has been read and the coeff have been read via MM
proc_common_wait_until_high(clk, tb_end_almost);
assert read_coefs_arr = ref_coefs_arr report "Coefs file does not match coefs read via MM" severity error;
wait;
end process;
 
---------------------------------------------------------------
-- DUT = Device Under Test
---------------------------------------------------------------
u_dut : entity work.fil_ppf_single
generic map (
g_fil_ppf => g_fil_ppf,
g_fil_ppf_pipeline => g_fil_ppf_pipeline,
g_file_index_arr => c_mif_file_index_arr,
g_coefs_file_prefix => c_mif_file_prefix
)
port map (
dp_clk => clk,
dp_rst => rst,
mm_clk => clk,
mm_rst => rst,
ram_coefs_mosi => ram_coefs_mosi,
ram_coefs_miso => ram_coefs_miso,
in_dat => in_dat,
in_val => in_val,
out_dat => out_dat,
out_val => out_val
);
 
---------------------------------------------------------------
-- VERIFY THE OUTPUT
---------------------------------------------------------------
p_verify_out_dat_width : process
begin
-- Wait until tb_end_almost to avoid that the Error message gets lost in earlier messages
proc_common_wait_until_high(clk, tb_end_almost);
assert g_fil_ppf.out_dat_w >= g_fil_ppf.coef_dat_w report "Output data width too small for coefficients" severity error;
wait;
end process;
p_verify_out_val_cnt : process
begin
-- Wait until tb_end_almost
proc_common_wait_until_high(clk, tb_end_almost);
-- The filter has a latency of 1 tap, so there remains in_dat for tap in the filter
assert in_val_cnt > 0 report "Test did not run, no valid input data" severity error;
assert out_val_cnt = in_val_cnt-c_nof_data_per_tap report "Unexpected number of valid output data coefficients" severity error;
wait;
end process;
in_val_cnt <= in_val_cnt+1 when rising_edge(clk) and in_val='1' else in_val_cnt;
out_val_cnt <= out_val_cnt+1 when rising_edge(clk) and out_val='1' else out_val_cnt;
ref_dat <= ref_dat_arr(out_val_cnt) WHEN out_val_cnt < c_nof_data_in_filter ELSE 0;
 
p_verify_out_dat : process(clk)
variable v_coeff : integer;
begin
if rising_edge(clk) then
if out_val='1' then
if g_fil_ppf.out_dat_w >= g_fil_ppf.coef_dat_w then
if g_fil_ppf.out_dat_w > g_fil_ppf.coef_dat_w then
v_coeff := ref_dat; -- positive input pulse
else
v_coeff := -ref_dat; -- compensate for full scale negative input pulse
end if;
for S in 0 to g_fil_ppf.nof_streams-1 loop
-- all streams carry the same data
assert TO_SINT(out_dat((S+1)*g_fil_ppf.out_dat_w-1 downto S*g_fil_ppf.out_dat_w)) = v_coeff report "Output data error" severity error;
end loop;
end if;
end if;
end if;
end process;
 
end tb;
/trunk/tb_fil_ppf_wide.vhd
0,0 → 1,357
-- Author: Harm Jan Pepping : hajee at astron.nl : April 2012
-- Eric Kooistra : kooistra at astron.nl: july 2016
--------------------------------------------------------------------------------
--
-- Copyright (C) 2012
-- 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/>.
--
--------------------------------------------------------------------------------
--
-- Purpose: Test bench for fil_ppf_wide.vhd
--
-- The DUT fil_ppf_wide.vhd has wb_factor >= 1 and uses array types and
-- wb_factor instances of fil_ppf_single.vhd.
--
-- See also description tb_fil_ppf_single.vhd.
--
-- Usage:
-- > run -all
-- > testbench is selftesting.
--
library ieee, common_pkg_lib, dp_pkg_lib, astron_diagnostics_lib, astron_ram_lib, astron_mm_lib;
use IEEE.std_logic_1164.all;
use IEEE.numeric_std.all;
use IEEE.std_logic_textio.all;
use std.textio.all;
use common_pkg_lib.common_pkg.all;
use astron_ram_lib.common_ram_pkg.ALL;
use common_pkg_lib.common_lfsr_sequences_pkg.ALL;
use common_pkg_lib.tb_common_pkg.all;
use astron_mm_lib.tb_common_mem_pkg.ALL;
use dp_pkg_lib.dp_stream_pkg.ALL;
use work.fil_pkg.all;
 
entity tb_fil_ppf_wide is
generic(
-- generics for tb
g_big_endian_wb_in : boolean := true;
g_big_endian_wb_out : boolean := true;
g_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
-- type t_fil_pipeline is record
-- -- generic for the taps and coefficients memory
-- mem_delay : natural; -- = 2
-- -- generics for the multiplier in in the filter unit
-- mult_input : natural; -- = 1
-- mult_product : natural; -- = 1
-- mult_output : natural; -- = 1
-- -- generics for the adder tree in in the filter unit
-- adder_stage : natural; -- = 1
-- -- generics for the requantizer in the filter unit
-- requant_remove_lsb : natural; -- = 1
-- requant_remove_msb : natural; -- = 0
-- end record;
g_fil_ppf : t_fil_ppf := (4, 1, 64, 8, 1, 0, 8, 23, 16);
-- type t_fil_ppf is record
-- wb_factor : natural; -- = 4, the wideband factor
-- nof_chan : natural; -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan
-- nof_bands : natural; -- = 1024, the number of polyphase channels (= number of points of the FFT)
-- nof_taps : natural; -- = 16, the number of FIR taps per subband
-- nof_streams : natural; -- = 1, the number of streams that are served by the same coefficients.
-- backoff_w : natural; -- = 0, number of bits for input backoff to avoid output overflow
-- in_dat_w : natural; -- = 8, number of input bits per stream
-- out_dat_w : natural; -- = 23, number of output bits (per stream). It is set to in_dat_w+coef_dat_w-1 = 23 to be sure the requantizer
-- does not remove any of the data in order to be able to verify with the original coefficients values.
-- coef_dat_w : natural; -- = 16, data width of the FIR coefficients
-- end record;
g_coefs_file_prefix : string := "hex/run_pfir_coeff_m_incrementing";
g_enable_in_val_gaps : boolean := FALSE
);
end entity tb_fil_ppf_wide;
 
architecture tb of tb_fil_ppf_wide is
constant c_clk_period : time := 10 ns;
constant c_nof_channels : natural := 2**g_fil_ppf.nof_chan;
constant c_nof_coefs : natural := g_fil_ppf.nof_taps * g_fil_ppf.nof_bands; -- nof PFIR coef
constant c_nof_coefs_per_wb : natural := c_nof_coefs / g_fil_ppf.wb_factor;
constant c_nof_data_in_filter : natural := c_nof_coefs * c_nof_channels; -- nof PFIR coef expanded for all channels
constant c_nof_data_per_tap : natural := c_nof_data_in_filter / g_fil_ppf.nof_taps;
constant c_nof_valid_in_filter : natural := c_nof_data_in_filter / g_fil_ppf.wb_factor;
constant c_nof_valid_per_tap : natural := c_nof_data_per_tap / g_fil_ppf.wb_factor;
constant c_nof_bands_per_mif : natural := g_fil_ppf.nof_bands / g_fil_ppf.wb_factor;
constant c_mif_coef_mem_addr_w : natural := ceil_log2(g_fil_ppf.nof_bands);
constant c_mif_coef_mem_span : natural := 2**c_mif_coef_mem_addr_w; -- mif coef mem span for one tap
 
constant c_coefs_file_prefix : string := g_coefs_file_prefix & "_" & integer'image(g_fil_ppf.nof_taps) & "taps" &
"_" & integer'image(g_fil_ppf.nof_bands) & "points" &
"_" & integer'image(g_fil_ppf.coef_dat_w) & "b";
constant c_mif_file_prefix : string := c_coefs_file_prefix & "_" & integer'image(g_fil_ppf.wb_factor) & "wb";
constant c_fil_prod_w : natural := g_fil_ppf.in_dat_w + g_fil_ppf.coef_dat_w - 1; -- skip double sign bit
constant c_fil_sum_w : natural := c_fil_prod_w; -- DC gain = 1
constant c_fil_lsb_w : natural := c_fil_sum_w - g_fil_ppf.out_dat_w; -- nof LSbits that get rounded for out_dat
constant c_in_ampl : natural := 2**c_fil_lsb_w; -- scale in_dat to compensate for rounding
constant c_gap_factor : natural := sel_a_b(g_enable_in_val_gaps, 3, 1);
-- input/output data width
constant c_in_dat_w : natural := g_fil_ppf.in_dat_w;
constant c_out_dat_w : natural := g_fil_ppf.out_dat_w;
 
type t_wb_integer_arr2 is array(integer range <>) of t_integer_arr(c_nof_valid_in_filter-1 downto 0);
-- signal definitions
signal tb_end : std_logic := '0';
signal tb_end_mm : std_logic := '0';
signal tb_end_almost : std_logic := '0';
signal clk : std_logic := '0';
signal rst : std_logic := '0';
signal random : std_logic_vector(15 DOWNTO 0) := (OTHERS=>'0'); -- use different lengths to have different random sequences
 
signal ram_coefs_mosi : t_mem_mosi := c_mem_mosi_rst;
signal ram_coefs_miso : t_mem_miso;
 
signal in_dat_arr : t_fil_slv_arr(g_fil_ppf.wb_factor*g_fil_ppf.nof_streams-1 downto 0); -- = t_slv_32_arr fits g_fil_ppf.in_dat_w <= 32
signal in_val : std_logic;
signal in_val_cnt : natural := 0;
signal in_gap : std_logic := '0';
signal out_dat_arr : t_fil_slv_arr(g_fil_ppf.wb_factor*g_fil_ppf.nof_streams-1 downto 0); -- = t_slv_32_arr fits g_fil_ppf.out_dat_w <= 32
signal out_val : std_logic;
signal out_val_cnt : natural := 0;
signal mif_coefs_arr : t_integer_arr(c_nof_bands_per_mif-1 downto 0) := (OTHERS=>0); -- = PFIR coef for 1 wb, 1 tap as read from 1 MIF file
signal mif_dat_arr2 : t_wb_integer_arr2(0 to g_fil_ppf.wb_factor-1) := (OTHERS=>(OTHERS=>0)); -- = PFIR coef for all taps as read from all MIF files and expanded for all channels
 
signal ref_coefs_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0); -- = PFIR coef for all taps as read from the coefs file
signal ref_dat_arr2 : t_wb_integer_arr2(0 to g_fil_ppf.wb_factor-1) := (OTHERS=>(OTHERS=>0)); -- = PFIR coef for all taps as read from the coefs file expanded for all channels
signal ref_dat_arr : t_integer_arr(0 to g_fil_ppf.wb_factor-1) := (OTHERS=>0);
 
signal read_coefs_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0); -- = PFIR coef for all taps as read via MM from the coefs memories
begin
 
clk <= (not clk) or tb_end after c_clk_period/2;
rst <= '1', '0' after c_clk_period*7;
random <= func_common_random(random) WHEN rising_edge(clk);
in_gap <= random(random'HIGH) WHEN g_enable_in_val_gaps=TRUE ELSE '0';
 
---------------------------------------------------------------
-- SEND IMPULSE TO THE DATA INPUT
---------------------------------------------------------------
p_send_impulse : process
begin
tb_end <= '0';
in_dat_arr <= (others=>(others=>'0'));
in_val <= '0';
proc_common_wait_until_low(clk, rst); -- Wait until reset has finished
proc_common_wait_some_cycles(clk, 10); -- Wait an additional amount of cycles
-- The impulse is high during the entire tap, so g_big_endian_wb_in has no impact on the wideband input order of index P
-- Pulse during first tap of all channels
for I in 0 to c_nof_valid_per_tap-1 loop
for P in 0 to g_fil_ppf.wb_factor-1 loop
for S in 0 to g_fil_ppf.nof_streams-1 loop
in_dat_arr(P*g_fil_ppf.nof_streams + S) <= TO_UVEC(c_in_ampl, c_fil_slv_w);
in_val <= '1';
end loop;
end loop;
in_val <= '1';
proc_common_wait_some_cycles(clk, 1);
if in_gap='1' then
in_val <= '0';
proc_common_wait_some_cycles(clk, 1);
end if;
end loop;
 
-- Zero during next nof_taps-1 blocks, +1 more to account for block latency of PPF and +1 more to have zeros output in last block
in_dat_arr <= (others=>(others=>'0'));
FOR J IN 0 TO g_fil_ppf.nof_taps-2 +1 +1 LOOP
FOR I IN 0 TO c_nof_valid_per_tap-1 LOOP
in_val <= '1';
proc_common_wait_some_cycles(clk, 1);
IF in_gap='1' THEN
in_val <= '0';
proc_common_wait_some_cycles(clk, 1);
END IF;
END LOOP;
END LOOP;
in_val <= '0';
 
-- Wait until done
proc_common_wait_some_cycles(clk, c_gap_factor*c_nof_valid_per_tap); -- PPF latency of 1 tap
proc_common_wait_until_high(clk, tb_end_mm); -- MM read done
tb_end_almost <= '1';
proc_common_wait_some_cycles(clk, 10);
tb_end <= '1';
WAIT;
END PROCESS;
---------------------------------------------------------------
-- CREATE REFERENCE ARRAY
---------------------------------------------------------------
p_create_ref_from_coefs_file : PROCESS
variable v_coefs_flip_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0);
begin
-- Read all coeffs from coefs file
proc_common_read_integer_file(c_coefs_file_prefix & ".dat", 0, c_nof_coefs, 1, ref_coefs_arr);
wait for 1 ns;
-- Reverse the coeffs per tap
for J in 0 to g_fil_ppf.nof_taps-1 loop
for I in 0 to g_fil_ppf.nof_bands-1 loop
v_coefs_flip_arr(J*g_fil_ppf.nof_bands + g_fil_ppf.nof_bands-1-I) := ref_coefs_arr(J*g_fil_ppf.nof_bands+I);
end loop;
end loop;
-- Distribute over wb_factor and expand the channels (for one stream)
for I in 0 to c_nof_coefs_per_wb-1 loop
for P in 0 to g_fil_ppf.wb_factor-1 loop
for K in 0 to c_nof_channels-1 loop
ref_dat_arr2(P)(I*c_nof_channels + K) <= TO_SINT(TO_SVEC(v_coefs_flip_arr(I*g_fil_ppf.wb_factor + P), g_fil_ppf.coef_dat_w));
end loop;
end loop;
end loop;
wait;
end process;
 
p_create_ref_from_mif_file : PROCESS
begin
for P in 0 to g_fil_ppf.wb_factor-1 loop
for J in 0 to g_fil_ppf.nof_taps-1 loop
-- Read coeffs per wb and per tap from MIF file
proc_common_read_mif_file(c_mif_file_prefix & "_" & integer'image(P*g_fil_ppf.nof_taps+J) & ".mif", mif_coefs_arr);
wait for 1 ns;
-- Expand the channels (for one stream)
for I in 0 to c_nof_bands_per_mif-1 loop
for K in 0 to c_nof_channels-1 loop
mif_dat_arr2(P)(J*c_nof_valid_per_tap + I*c_nof_channels + K) <= TO_SINT(TO_SVEC(mif_coefs_arr(I), g_fil_ppf.coef_dat_w));
end loop;
end loop;
end loop;
end loop;
wait;
end process;
 
p_coefs_memory_read : process
variable v_mif_index : natural;
variable v_mif_base : natural;
variable v_coef_offset : natural;
variable v_coef_index : natural;
begin
ram_coefs_mosi <= c_mem_mosi_rst;
for P in 0 to g_fil_ppf.wb_factor-1 loop
for J in 0 to g_fil_ppf.nof_taps-1 loop
v_mif_index := P*g_fil_ppf.nof_taps+J;
v_mif_base := v_mif_index*c_mif_coef_mem_span;
v_coef_offset := g_fil_ppf.nof_bands*(J+1)-1-P; -- coeff in MIF are in flipped order, unflip this in v_coef_index
for I in 0 to c_nof_bands_per_mif-1 loop
proc_mem_mm_bus_rd(v_mif_base+I, clk, ram_coefs_miso, ram_coefs_mosi);
proc_mem_mm_bus_rd_latency(1, clk);
v_coef_index := v_coef_offset - I*g_fil_ppf.wb_factor;
read_coefs_arr(v_coef_index) <= TO_SINT(ram_coefs_miso.rddata(g_fil_ppf.coef_dat_w-1 DOWNTO 0));
end loop;
end loop;
end loop;
proc_common_wait_some_cycles(clk, 1);
tb_end_mm <= '1';
wait;
end process;
 
---------------------------------------------------------------
-- DUT = Device Under Test
---------------------------------------------------------------
u_dut : entity work.fil_ppf_wide
generic map (
g_big_endian_wb_in => g_big_endian_wb_in,
g_big_endian_wb_out => g_big_endian_wb_out,
g_fil_ppf => g_fil_ppf,
g_fil_ppf_pipeline => g_fil_ppf_pipeline,
g_coefs_file_prefix => c_mif_file_prefix
)
port map (
dp_clk => clk,
dp_rst => rst,
mm_clk => clk,
mm_rst => rst,
ram_coefs_mosi => ram_coefs_mosi,
ram_coefs_miso => ram_coefs_miso,
in_dat_arr => in_dat_arr,
in_val => in_val,
out_dat_arr => out_dat_arr,
out_val => out_val
);
-- Verify the output of the DUT with the expected output from the reference array
p_verify_out_dat_width : process
begin
-- Wait until tb_end_almost to avoid that the Error message gets lost in earlier messages
proc_common_wait_until_high(clk, tb_end_almost);
assert g_fil_ppf.out_dat_w >= g_fil_ppf.coef_dat_w report "Output data width too small for coefficients" severity error;
wait;
end process;
p_verify_out_val_cnt : process
begin
-- Wait until tb_end_almost
proc_common_wait_until_high(clk, tb_end_almost);
-- The filter has a latency of 1 tap, so there remains in_dat for tap in the filter
assert in_val_cnt > 0 report "Test did not run, no valid input data" severity error;
assert out_val_cnt = in_val_cnt-c_nof_valid_per_tap report "Unexpected number of valid output data coefficients" severity error;
wait;
end process;
in_val_cnt <= in_val_cnt+1 when rising_edge(clk) and in_val='1' else in_val_cnt;
out_val_cnt <= out_val_cnt+1 when rising_edge(clk) and out_val='1' else out_val_cnt;
gen_ref_dat_arr : for P in 0 to g_fil_ppf.wb_factor-1 generate
ref_dat_arr(P) <= ref_dat_arr2(P)(out_val_cnt) when out_val_cnt < c_nof_valid_in_filter else 0;
end generate;
p_verify_out_dat : process(clk)
variable v_coeff : integer;
variable vP : natural;
begin
if rising_edge(clk) then
if out_val='1' then
for P in 0 to g_fil_ppf.wb_factor-1 loop
-- Adjust index for v_coeff dependend on g_big_endian_wb_out over all wb and streams for out_dat_arr,
-- because ref_dat_arr for 1 stream uses little endian time [0,1,2,3] to P [0,1,2,3] index mapping
if g_big_endian_wb_out=false then
vP := P;
else
vP := g_fil_ppf.wb_factor-1-P;
end if;
-- Output data width must be large enough to fit the coefficients width, this is verified by p_verify_out_dat_width
-- If g_fil_ppf.out_dat_w = g_fil_ppf.coef_dat_w then full scale input is simulated as negative due to that +2**(w-1)
-- wraps to -2**(w-1), so then compensate for that here.
if g_fil_ppf.out_dat_w > g_fil_ppf.coef_dat_w then
v_coeff := ref_dat_arr(vP); -- positive input pulse
else
v_coeff := -ref_dat_arr(vP); -- compensate for full scale negative input pulse
end if;
for S in 0 to g_fil_ppf.nof_streams-1 loop
-- all streams carry the same data
assert TO_SINT(out_dat_arr(P*g_fil_ppf.nof_streams + S)) = v_coeff report "Output data error" severity error;
end loop;
end loop;
end if;
end if;
end process;
 
end tb;
/trunk/tb_fil_ppf_wide_file_data.vhd
0,0 → 1,492
-- Author: Eric Kooistra : kooistra at astron.nl: july 2016
--------------------------------------------------------------------------------
--
-- Copyright (C) 2016
-- 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/>.
--
--------------------------------------------------------------------------------
--
-- Purpose: Test bench for fil_ppf_wide.vhd using file data
--
-- The DUT fil_ppf_wide.vhd has wb_factor >= 1 and uses array types and
-- wb_factor instances of fil_ppf_single.vhd.
--
-- Usage:
-- The g_coefs_file_prefix dat-file and g_data_file dat-file are created by
-- the Matlab script:
--
-- $RADIOHDL_WORK/applications/apertif/matlab/run_pfir.m
--
-- yields:
--
-- . g_coefs_file_prefix : run_pfir_m_pfir_coeff_fircls1_16taps_128points_16b.dat
-- . g_data_file : run_pfir_m_sinusoid_chirp_8b_16taps_128points_16b_16b.dat
--
-- The g_fil_ppf parameters nof_taps, nof_bands (= nof polyphase), c_in_dat_w,
-- out_dat_w and coef_dat_w must match the settings in run_pfir.m.
--
-- The g_fil_ppf.in_dat_w = 8 bit to fit run_pfir_m_sinusoid_chirp_wg_8b.dat. The
-- g_fil_ppf.backoff_w = 1 is necessary to accommodate the factor 2 overshoot that
-- the PFIR output can have.
--
-- The g_data_file contains a header followed by the PFIR coefficients, WG
-- data, PFIR data and PFFT data. The tb verifies that the PFIR coefficients
-- are the same as in the dat-fil indicated by g_coefs_file_prefix. The PFFT
-- data is not used in this tb.
--
-- The MIF files are generated from the g_coefs_file_prefix dat-file by
-- the Python script:
--
-- $RADIOHDL_WORK/libraries/dsp/filter/src/python/
-- python fil_ppf_create_mifs.py -f ../hex/run_pfir_m_pfir_coeff_fircls1_16taps_128points_16b.dat -t 16 -p 128 -w 1 -c 16
-- python fil_ppf_create_mifs.py -f ../hex/run_pfir_m_pfir_coeff_fircls1_16taps_128points_16b.dat -t 16 -p 128 -w 4 -c 16
--
-- yields:
--
-- . run_pfir_m_pfir_coeff_fircls1_16taps_128points_16b_1wb_#.mif, where # = 0:15
-- . run_pfir_m_pfir_coeff_fircls1_16taps_128points_16b_4wb_#.mif, where # = 0:64
--
-- The PFIR coefficient dat and mif files are kept in local ../hex
-- The input and expected output dat files are kept in local ../data.
--
-- The dat files that are created by Matlab first need to be copied manually
-- to these local directories and then the mif files need to be generated.
-- The modelsim_copy_files key in the hdllib.cfg will copy these files to the
-- build directory from where they are loaded by Modelsim.
--
-- > run -all
-- > testbench is selftesting.
-- > observe the *_scope as radix decimal, format analogue format signals
-- in the Wave window
--
library ieee, common_pkg_lib, dp_pkg_lib, astron_diagnostics_lib, astron_ram_lib, astron_mm_lib, astron_sim_tools_lib;
use IEEE.std_logic_1164.all;
use IEEE.numeric_std.all;
use IEEE.std_logic_textio.all;
use std.textio.all;
use common_pkg_lib.common_pkg.all;
use astron_ram_lib.common_ram_pkg.ALL;
use common_pkg_lib.common_lfsr_sequences_pkg.ALL;
use common_pkg_lib.tb_common_pkg.all;
use astron_mm_lib.tb_common_mem_pkg.ALL;
use dp_pkg_lib.dp_stream_pkg.ALL;
use work.fil_pkg.all;
 
entity tb_fil_ppf_wide_file_data is
generic(
-- generics for tb
g_big_endian_wb_in : boolean := true;
g_big_endian_wb_out : boolean := true;
g_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
-- type t_fil_pipeline is record
-- -- generic for the taps and coefficients memory
-- mem_delay : natural; -- = 2
-- -- generics for the multiplier in in the filter unit
-- mult_input : natural; -- = 1
-- mult_product : natural; -- = 1
-- mult_output : natural; -- = 1
-- -- generics for the adder tree in in the filter unit
-- adder_stage : natural; -- = 1
-- -- generics for the requantizer in the filter unit
-- requant_remove_lsb : natural; -- = 1
-- requant_remove_msb : natural; -- = 0
-- end record;
g_fil_ppf : t_fil_ppf := (4, 0, 128, 16, 2, 1, 8, 16, 16);
-- type t_fil_ppf is record
-- wb_factor : natural; -- = 4, the wideband factor
-- nof_chan : natural; -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan
-- nof_bands : natural; -- = 1024, the number of polyphase channels (= number of points of the FFT)
-- nof_taps : natural; -- = 16, the number of FIR taps per subband
-- nof_streams : natural; -- = 1, the number of streams that are served by the same coefficients.
-- backoff_w : natural; -- = 0, number of bits for input backoff to avoid output overflow
-- in_dat_w : natural; -- = 8, number of input bits per stream
-- out_dat_w : natural; -- = 16, number of output bits (per stream)
-- coef_dat_w : natural; -- = 16, data width of the FIR coefficients
-- end record;
g_coefs_file_prefix : string := "hex/run_pfir_m_pfir_coeff_fircls1";
g_data_file : string := "data/run_pfir_m_sinusoid_chirp_8b_16taps_128points_16b_16b.dat"; -- coefs, input and output data for 1 stream
g_data_file_nof_lines : natural := 25600; -- number of lines with input data that is available in the g_data_file
 
g_data_file_nof_read : natural := 5000; -- number of lines with input data to read and simulate, must be <= g_data_file_nof_lines
g_enable_in_val_gaps : boolean := FALSE
);
end entity tb_fil_ppf_wide_file_data;
 
architecture tb of tb_fil_ppf_wide_file_data is
 
constant c_clk_period : time := 10 ns;
constant c_sclk_period : time := c_clk_period / g_fil_ppf.wb_factor;
 
constant c_diff_margin : integer := 0; -- maximum difference between PFIR HDL output and expected output (> 0 to allow minor rounding differences)
 
constant c_nof_channels : natural := 2**g_fil_ppf.nof_chan;
constant c_nof_coefs : natural := g_fil_ppf.nof_taps * g_fil_ppf.nof_bands; -- nof PFIR coef
constant c_nof_data_per_block : natural := g_fil_ppf.nof_bands * c_nof_channels; -- 1 block corresponds to 1 tap
constant c_nof_valid_per_block : natural := c_nof_data_per_block / g_fil_ppf.wb_factor;
 
constant c_rnd_factor : natural := sel_a_b(g_enable_in_val_gaps, 3, 1);
constant c_dut_block_latency : natural := 2;
constant c_dut_clk_latency : natural := c_nof_valid_per_block * c_dut_block_latency * c_rnd_factor; -- worst case
 
-- input/output data width
constant c_in_dat_w : natural := g_fil_ppf.in_dat_w;
constant c_out_dat_w : natural := g_fil_ppf.out_dat_w;
 
-- PFIR coefficients file access
constant c_coefs_dat_file_prefix : string := g_coefs_file_prefix & "_" & integer'image(g_fil_ppf.nof_taps) & "taps" &
"_" & integer'image(g_fil_ppf.nof_bands) & "points" &
"_" & integer'image(g_fil_ppf.coef_dat_w) & "b";
constant c_coefs_mif_file_prefix : string := c_coefs_dat_file_prefix & "_" & integer'image(g_fil_ppf.wb_factor) & "wb";
 
-- Data file access
constant c_nof_lines_pfir_coefs : natural := c_nof_coefs;
constant c_nof_lines_wg_dat : natural := g_data_file_nof_lines;
constant c_nof_lines_pfir_dat : natural := c_nof_lines_wg_dat;
constant c_nof_lines_header : natural := 4;
constant c_nof_lines_header_wg : natural := c_nof_lines_header + c_nof_lines_pfir_coefs;
constant c_nof_lines_header_pfir : natural := c_nof_lines_header + c_nof_lines_pfir_coefs + c_nof_lines_wg_dat;
-- signal definitions
signal tb_end : std_logic := '0';
signal tb_end_almost : std_logic := '0';
signal clk : std_logic := '0';
signal sclk : std_logic := '1';
signal rst : std_logic := '0';
signal random : std_logic_vector(15 DOWNTO 0) := (OTHERS=>'0'); -- use different lengths to have different random sequences
 
signal coefs_dat_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0); -- = PFIR coef for all taps as read from via c_coefs_dat_file_prefix
signal coefs_ref_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0); -- = PFIR coef for all taps as read from via g_data_file
signal expected_data_arr : t_integer_arr(0 to g_data_file_nof_read-1) := (OTHERS=>0);
signal input_data_arr : t_integer_arr(0 to g_data_file_nof_read-1) := (OTHERS=>0);
signal input_data : std_logic_vector(g_fil_ppf.wb_factor*c_in_dat_w-1 DOWNTO 0);
signal input_data_scope : integer;
 
signal in_dat_arr : t_fil_slv_arr(g_fil_ppf.wb_factor*g_fil_ppf.nof_streams-1 downto 0); -- = t_slv_32_arr fits g_fil_ppf.in_dat_w <= 32
signal in_val : std_logic;
signal in_val_cnt : natural := 0;
signal in_sub_val : std_logic;
signal in_sub_val_cnt : natural := 0;
signal in_gap : std_logic := '0';
 
signal tsub : integer := 0; -- subband time counter
signal exp_data : std_logic_vector(g_fil_ppf.wb_factor*c_out_dat_w-1 DOWNTO 0);
signal exp_data_scope : integer;
signal diff_data_scope : integer;
signal output_data_scope : integer;
signal output_data : std_logic_vector(g_fil_ppf.wb_factor*c_out_dat_w-1 DOWNTO 0);
signal out_dat_arr : t_fil_slv_arr(g_fil_ppf.wb_factor*g_fil_ppf.nof_streams-1 downto 0); -- = t_slv_32_arr fits g_fil_ppf.out_dat_w <= 32
signal out_val : std_logic;
signal out_val_cnt : natural := 0;
signal out_sub_val : std_logic;
signal out_sub_val_cnt : natural := 0;
 
begin
 
sclk <= (not sclk) or tb_end after c_sclk_period/2;
clk <= (not clk) or tb_end after c_clk_period/2;
rst <= '1', '0' after c_clk_period*7;
random <= func_common_random(random) WHEN rising_edge(clk);
in_gap <= random(random'HIGH) WHEN g_enable_in_val_gaps=TRUE ELSE '0';
 
---------------------------------------------------------------
-- DATA INPUT
---------------------------------------------------------------
--
-- In this testbench use:
--
-- parallel serial type
-- in_dat_arr [wb_factor][nof_streams] [t][nof_channels] int
--
-- The time to wb_factor mapping for the fil_ppf_wide is big endian,
-- so [3:0] = [t0,t1,t2,t3], when g_big_endian_wb_in = TRUE.
-- When wb_factor = 4 and nof_streams = 2 then the mapping is as
-- follows (S = stream index, P = wideband factor index):
--
-- t P S
-- 0 3 0
-- 0 3 1
-- 1 2 0
-- 1 2 1
-- 2 1 0
-- 2 1 1
-- 3 0 0
-- 3 0 1
p_input_stimuli : process
variable vP : natural;
begin
-- read input data from file
proc_common_read_integer_file(g_data_file, c_nof_lines_header_wg, g_data_file_nof_read, 1, input_data_arr);
wait for 1 ns;
tb_end <= '0';
in_dat_arr <= (others=>(others=>'0'));
in_val <= '0';
proc_common_wait_until_low(clk, rst); -- Wait until reset has finished
proc_common_wait_some_cycles(clk, 10); -- Wait an additional amount of cycles
 
-- apply stimuli
for I in 0 to g_data_file_nof_read/g_fil_ppf.wb_factor-1 loop -- serial
for K in 0 to c_nof_channels-1 loop -- serial
for P in 0 to g_fil_ppf.wb_factor-1 loop -- parallel
if g_big_endian_wb_in=TRUE then
vP := g_fil_ppf.wb_factor-1-P; -- time to wideband big endian
else
vP := P; -- time to wideband little endian
end if;
for S in 0 to g_fil_ppf.nof_streams-1 loop -- parallel
if S=1 then
-- if present then stream 1 carries zero data to be able to recognize the stream order in the wave window
in_dat_arr(vP*g_fil_ppf.nof_streams + S) <= (OTHERS=>'0');
else
-- stream 0 and if present the other streams >= 2 carry the same input reference data to verify the filter function
in_dat_arr(vP*g_fil_ppf.nof_streams + S) <= TO_SVEC(input_data_arr(I*g_fil_ppf.wb_factor + P), c_fil_slv_w);
end if;
in_val <= '1';
end loop;
end loop;
in_val <= '1';
proc_common_wait_some_cycles(clk, 1);
if in_gap='1' then
in_val <= '0';
proc_common_wait_some_cycles(clk, 1);
end if;
end loop;
end loop;
 
-- Wait until done
in_val <= '0';
proc_common_wait_some_cycles(clk, c_dut_clk_latency); -- wait for at least PPF latency of 1 tap
tb_end_almost <= '1';
proc_common_wait_some_cycles(clk, 100);
tb_end <= '1';
wait;
end process;
 
---------------------------------------------------------------
-- DUT = Device Under Test
---------------------------------------------------------------
u_dut : entity work.fil_ppf_wide
generic map (
g_big_endian_wb_in => g_big_endian_wb_in,
g_big_endian_wb_out => g_big_endian_wb_out,
g_fil_ppf => g_fil_ppf,
g_fil_ppf_pipeline => g_fil_ppf_pipeline,
g_coefs_file_prefix => c_coefs_mif_file_prefix
)
port map (
dp_clk => clk,
dp_rst => rst,
mm_clk => clk,
mm_rst => rst,
ram_coefs_mosi => c_mem_mosi_rst,
ram_coefs_miso => OPEN,
in_dat_arr => in_dat_arr,
in_val => in_val,
out_dat_arr => out_dat_arr,
out_val => out_val
);
 
---------------------------------------------------------------
-- Verify PFIR coefficients
---------------------------------------------------------------
p_verify_pfir_coefs_files : PROCESS
begin
-- Verify that the PFIR coefficients in g_data_file are the same as those in c_coefs_dat_file_prefix.dat
-- Just assume that the c_coefs_dat_file_prefix.dat is the same as the PFIR coefficients that are loaded via the MIFs,
-- so do not read back the PFIR coefficients via MM.
proc_common_read_integer_file(c_coefs_dat_file_prefix & ".dat", 0, c_nof_coefs, 1, coefs_dat_arr);
proc_common_read_integer_file(g_data_file, c_nof_lines_header, c_nof_coefs, 1, coefs_ref_arr);
wait for 1 ns;
-- Wait until tb_end_almost to avoid that the Error message gets lost in earlier messages
proc_common_wait_until_high(clk, tb_end_almost);
assert coefs_dat_arr = coefs_ref_arr report "Unexpected PFIR coefficients." severity error;
wait;
end process;
 
---------------------------------------------------------------
-- VERIFY OUTPUT
---------------------------------------------------------------
p_verify_out_val_cnt : process
begin
-- Wait until tb_end_almost
proc_common_wait_until_high(clk, tb_end_almost);
-- The filter has a latency of 1 tap, so there remains in_dat for tap in the filter
assert in_val_cnt > 0 report "Test did not run, no valid input data" severity error;
assert out_val_cnt = in_val_cnt-c_nof_valid_per_block report "Unexpected number of valid output data" severity error;
wait;
end process;
 
tsub <= tsub+1 when rising_edge(clk) and in_sub_val='1' and in_sub_val_cnt > 0 and (in_sub_val_cnt MOD c_nof_valid_per_block = 0);
 
in_sub_val <= '1' when in_val='1' and (in_val_cnt mod c_nof_channels)=0 else '0';
out_sub_val <= '1' when out_val='1' and (out_val_cnt mod c_nof_channels)=0 else '0';
in_sub_val_cnt <= in_val_cnt/c_nof_channels;
out_sub_val_cnt <= out_val_cnt/c_nof_channels;
 
in_val_cnt <= in_val_cnt+1 when rising_edge(clk) and in_val='1' else in_val_cnt;
out_val_cnt <= out_val_cnt+1 when rising_edge(clk) and out_val='1' else out_val_cnt;
 
p_expected_output : process
begin
-- read expected output data from file
proc_common_read_integer_file(g_data_file, c_nof_lines_header_pfir, g_data_file_nof_read, 1, expected_data_arr);
wait;
end process;
 
p_verify_output : process(clk)
variable vI : natural := 0;
variable vK : natural := 0;
variable vP : natural;
variable v_out_dat : integer;
variable v_exp_dat : integer;
begin
if rising_edge(clk) then
if out_val='1' then
for P in 0 to g_fil_ppf.wb_factor-1 loop -- parallel
if g_big_endian_wb_out=true then
vP := g_fil_ppf.wb_factor-1-P; -- time to wideband big endian
else
vP := P; -- time to wideband little endian
end if;
for S in 0 to g_fil_ppf.nof_streams-1 loop -- parallel
v_out_dat := TO_SINT(out_dat_arr(vP*g_fil_ppf.nof_streams + S));
if S=1 then
-- stream 1 carries zero data
v_exp_dat := 0;
assert v_out_dat = v_exp_dat report "Output data error (stream 1 not zero)" severity error;
else
-- stream 0 and all other streams >= 2 carry the same data
v_exp_dat := expected_data_arr(vI*g_fil_ppf.wb_factor + P);
assert v_out_dat <= v_exp_dat + c_diff_margin and
v_out_dat >= v_exp_dat - c_diff_margin report "Output data error" severity error;
end if;
end loop;
end loop;
if vK < c_nof_channels-1 then -- serial
vK := vK + 1;
else
vK := 0;
vI := vI + 1;
end if;
end if;
end if;
end process;
 
---------------------------------------------------------------
-- DATA SCOPES
---------------------------------------------------------------
p_input_data : process(in_dat_arr)
constant cS : natural := 0; -- tap the input_data from stream 0
begin
for P in 0 to g_fil_ppf.wb_factor-1 loop
input_data((P+1)*c_in_dat_w-1 downto P*c_in_dat_w) <= in_dat_arr(P*g_fil_ppf.nof_streams + cS)(c_in_dat_w-1 downto 0);
end loop;
end process;
 
p_output_data : process(out_dat_arr)
variable cS : natural; -- tap the output_data from stream 0
begin
for P in 0 to g_fil_ppf.wb_factor-1 loop
output_data((P+1)*c_out_dat_w-1 DOWNTO P*c_out_dat_w) <= out_dat_arr(P*g_fil_ppf.nof_streams + cS)(c_out_dat_w-1 downto 0);
end loop;
end process;
 
p_exp_data : process(expected_data_arr, out_sub_val_cnt)
variable vP : natural;
begin
for P in 0 to g_fil_ppf.wb_factor-1 loop
if g_big_endian_wb_out=true then
vP := g_fil_ppf.wb_factor-1-P;
else
vP := P;
end if;
exp_data((vP+1)*c_out_dat_w-1 DOWNTO vP*c_out_dat_w) <= TO_SVEC(expected_data_arr(out_sub_val_cnt*g_fil_ppf.wb_factor + P), c_out_dat_w);
end loop;
end process;
 
u_input_data_scope : entity astron_sim_tools_lib.common_wideband_data_scope
generic map (
g_sim => TRUE,
g_wideband_factor => g_fil_ppf.wb_factor, -- Wideband rate factor = 4 for dp_clk processing frequency is 200 MHz frequency and SCLK sample frequency Fs is 800 MHz
g_wideband_big_endian => g_big_endian_wb_in, -- When true in_data[3:0] = sample[t0,t1,t2,t3], else when false : in_data[3:0] = sample[t3,t2,t1,t0]
g_dat_w => c_in_dat_w -- Actual width of the data samples
)
port map (
-- Sample clock
SCLK => sclk, -- sample clk, use only for simulation purposes
 
-- Streaming input data
in_data => input_data,
in_val => in_val,
 
-- Scope output samples
out_dat => OPEN,
out_int => input_data_scope
);
 
u_exp_data_scope : entity astron_sim_tools_lib.common_wideband_data_scope
generic map (
g_sim => TRUE,
g_wideband_factor => g_fil_ppf.wb_factor, -- Wideband rate factor = 4 for dp_clk processing frequency is 200 MHz frequency and SCLK sample frequency Fs is 800 MHz
g_wideband_big_endian => g_big_endian_wb_out, -- When true in_data[3:0] = sample[t0,t1,t2,t3], else when false : in_data[3:0] = sample[t3,t2,t1,t0]
g_dat_w => c_out_dat_w -- Actual width of the data samples
)
port map (
-- Sample clock
SCLK => sclk, -- sample clk, use only for simulation purposes
 
-- Streaming input data
in_data => exp_data,
in_val => out_val,
 
-- Scope output samples
out_dat => OPEN,
out_int => exp_data_scope
);
 
u_output_data_scope : entity astron_sim_tools_lib.common_wideband_data_scope
generic map (
g_sim => TRUE,
g_wideband_factor => g_fil_ppf.wb_factor, -- Wideband rate factor = 4 for dp_clk processing frequency is 200 MHz frequency and SCLK sample frequency Fs is 800 MHz
g_wideband_big_endian => g_big_endian_wb_out, -- When true in_data[3:0] = sample[t0,t1,t2,t3], else when false : in_data[3:0] = sample[t3,t2,t1,t0]
g_dat_w => c_out_dat_w -- Actual width of the data samples
)
port map (
-- Sample clock
SCLK => sclk, -- sample clk, use only for simulation purposes
 
-- Streaming input data
in_data => output_data,
in_val => out_val,
 
-- Scope output samples
out_dat => OPEN,
out_int => output_data_scope
);
 
diff_data_scope <= exp_data_scope - output_data_scope;
 
-- Equivalent to p_verify_output, but using the sclk scope data
p_verify_data_scope : process(sclk)
begin
if rising_edge(clk) then
assert diff_data_scope <= c_diff_margin and
diff_data_scope >= -c_diff_margin report "Output data scope error" severity error;
end if;
end process;
 
end tb;
/trunk/tb_tb_fil_ppf_single.vhd
0,0 → 1,82
--------------------------------------------------------------------------------
--
-- Copyright (C) 2016
-- 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/>.
--
--------------------------------------------------------------------------------
 
-- Purpose: Multi-testbench for fil_ppf_single
-- Description:
-- Verify fil_ppf_single
-- Usage:
-- > as 4
-- > run -all
 
LIBRARY IEEE, common_pkg_lib;
USE IEEE.std_logic_1164.ALL;
USE common_pkg_lib.common_pkg.all;
USE work.fil_pkg.all;
 
ENTITY tb_tb_fil_ppf_single IS
END tb_tb_fil_ppf_single;
 
ARCHITECTURE tb OF tb_tb_fil_ppf_single IS
CONSTANT c_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
CONSTANT c_prefix : string := "hex/run_pfir_coeff_m_incrementing";
SIGNAL tb_end : STD_LOGIC := '0'; -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
BEGIN
 
--g_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
-- -- type t_fil_pipeline is record
-- -- -- generic for the taps and coefficients memory
-- -- mem_delay : natural; -- = 2
-- -- -- generics for the multiplier in in the filter unit
-- -- mult_input : natural; -- = 1
-- -- mult_product : natural; -- = 1
-- -- mult_output : natural; -- = 1
-- -- -- generics for the adder tree in in the filter unit
-- -- adder_stage : natural; -- = 1
-- -- -- generics for the requantizer in the filter unit
-- -- requant_remove_lsb : natural; -- = 1
-- -- requant_remove_msb : natural; -- = 0
-- -- end record;
--g_fil_ppf : t_fil_ppf := (1, 1, 64, 8, 1, 8, 20, 16);
-- -- type t_fil_ppf is record
-- -- wb_factor : natural; -- = 1, the wideband factor
-- -- nof_chan : natural; -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan
-- -- nof_bands : natural; -- = 128, the number of polyphase channels (= number of points of the FFT)
-- -- nof_taps : natural; -- = 16, the number of FIR taps per subband
-- -- nof_streams : natural; -- = 1, the number of streams that are served by the same coefficients.
-- -- backoff_w : natural; -- = 0, number of bits for input backoff to avoid output overflow
-- -- in_dat_w : natural; -- = 8, number of input bits per stream
-- -- out_dat_w : natural; -- = 23, number of output bits (per stream). It is set to in_dat_w+coef_dat_w-1 = 23 to be sure the requantizer
-- -- does not remove any of the data in order to be able to verify with the original coefficients values.
-- -- coef_dat_w : natural; -- = 16, data width of the FIR coefficients
-- -- end record;
--g_coefs_file_prefix : string := "hex/run_pfir_coeff_m_incrementing";
--g_enable_in_val_gaps : boolean := FALSE
 
u_act : ENTITY work.tb_fil_ppf_single GENERIC MAP ((1, 1, 1, 1, 1, 1, 0), (1, 0, 64, 8, 1, 0, 8, 23, 16), c_prefix, FALSE);
u_rnd_quant : ENTITY work.tb_fil_ppf_single GENERIC MAP ((1, 1, 1, 1, 1, 1, 0), (1, 0, 64, 8, 1, 0, 8, 16, 16), c_prefix, TRUE);
u_rnd_9taps : ENTITY work.tb_fil_ppf_single GENERIC MAP ((1, 1, 1, 1, 1, 1, 0), (1, 0, 64, 9, 1, 0, 8, 17, 16), c_prefix, TRUE);
u_rnd_3streams : ENTITY work.tb_fil_ppf_single GENERIC MAP ((1, 1, 1, 1, 1, 1, 0), (1, 0, 64, 9, 3, 0, 8, 18, 16), c_prefix, TRUE);
u_rnd_4channels : ENTITY work.tb_fil_ppf_single GENERIC MAP ((1, 1, 1, 1, 1, 1, 0), (1, 2, 64, 9, 3, 0, 8, 22, 16), c_prefix, TRUE);
END tb;
/trunk/tb_tb_fil_ppf_wide.vhd
0,0 → 1,94
--------------------------------------------------------------------------------
--
-- Copyright (C) 2016
-- 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/>.
--
--------------------------------------------------------------------------------
 
-- Purpose: Multi-testbench for fil_ppf_wide
-- Description:
-- Verify fil_ppf_wide
-- Usage:
-- > as 4
-- > run -all
 
LIBRARY IEEE, common_pkg_lib;
USE IEEE.std_logic_1164.ALL;
USE common_pkg_lib.common_pkg.all;
USE work.fil_pkg.all;
 
ENTITY tb_tb_fil_ppf_wide IS
END tb_tb_fil_ppf_wide;
 
ARCHITECTURE tb OF tb_tb_fil_ppf_wide IS
CONSTANT c_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
CONSTANT c_prefix : string := "hex/run_pfir_coeff_m_incrementing";
SIGNAL tb_end : STD_LOGIC := '0'; -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
BEGIN
 
--g_big_endian_wb_in : boolean := true;
--g_big_endian_wb_out : boolean := true;
--g_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
-- -- type t_fil_pipeline is record
-- -- -- generic for the taps and coefficients memory
-- -- mem_delay : natural; -- = 2
-- -- -- generics for the multiplier in in the filter unit
-- -- mult_input : natural; -- = 1
-- -- mult_product : natural; -- = 1
-- -- mult_output : natural; -- = 1
-- -- -- generics for the adder tree in in the filter unit
-- -- adder_stage : natural; -- = 1
-- -- -- generics for the requantizer in the filter unit
-- -- requant_remove_lsb : natural; -- = 1
-- -- requant_remove_msb : natural; -- = 0
-- -- end record;
--g_fil_ppf : t_fil_ppf := (1, 1, 64, 8, 1, 8, 20, 16);
-- -- type t_fil_ppf is record
-- -- wb_factor : natural; -- = 1, the wideband factor
-- -- nof_chan : natural; -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan
-- -- nof_bands : natural; -- = 128, the number of polyphase channels (= number of points of the FFT)
-- -- nof_taps : natural; -- = 16, the number of FIR taps per subband
-- -- nof_streams : natural; -- = 1, the number of streams that are served by the same coefficients.
-- -- backoff_w : natural; -- = 0, number of bits for input backoff to avoid output overflow
-- -- in_dat_w : natural; -- = 8, number of input bits per stream
-- -- out_dat_w : natural; -- = 23, number of output bits (per stream). It is set to in_dat_w+coef_dat_w-1 = 23 to be sure the requantizer
-- -- does not remove any of the data in order to be able to verify with the original coefficients values.
-- -- coef_dat_w : natural; -- = 16, data width of the FIR coefficients
-- -- end record;
--g_coefs_file_prefix : string := "hex/run_pfir_coeff_m_incrementing";
--g_enable_in_val_gaps : boolean := FALSE
 
-- verify fil_ppf_wide for wb_factor=1, so effectively same as using fil_ppf_single directly
u1_act : ENTITY work.tb_fil_ppf_wide GENERIC MAP (TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (1, 0, 64, 8, 1, 0, 8, 23, 16), c_prefix, FALSE);
u1_rnd_quant : ENTITY work.tb_fil_ppf_wide GENERIC MAP (TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (1, 0, 64, 8, 1, 0, 8, 16, 16), c_prefix, TRUE);
u1_rnd_9taps : ENTITY work.tb_fil_ppf_wide GENERIC MAP (TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (1, 0, 64, 9, 1, 0, 8, 17, 16), c_prefix, TRUE);
u1_rnd_3streams : ENTITY work.tb_fil_ppf_wide GENERIC MAP (TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (1, 0, 64, 9, 3, 0, 8, 18, 16), c_prefix, TRUE);
u1_rnd_4channels : ENTITY work.tb_fil_ppf_wide GENERIC MAP (TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (1, 2, 64, 9, 3, 0, 8, 22, 16), c_prefix, TRUE);
-- verify fil_ppf_wide for wb_factor>1
u4_act : ENTITY work.tb_fil_ppf_wide GENERIC MAP ( TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (4, 0, 64, 8, 1, 0, 8, 23, 16), c_prefix, FALSE);
u4_act_be_le : ENTITY work.tb_fil_ppf_wide GENERIC MAP ( TRUE, FALSE, (1, 1, 1, 1, 1, 1, 0), (4, 0, 64, 8, 1, 0, 8, 23, 16), c_prefix, FALSE);
u4_act_le_le : ENTITY work.tb_fil_ppf_wide GENERIC MAP (FALSE, FALSE, (1, 1, 1, 1, 1, 1, 0), (4, 0, 64, 8, 1, 0, 8, 23, 16), c_prefix, FALSE);
u4_rnd_quant : ENTITY work.tb_fil_ppf_wide GENERIC MAP ( TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (4, 0, 64, 8, 1, 0, 8, 16, 16), c_prefix, TRUE);
u4_rnd_9taps : ENTITY work.tb_fil_ppf_wide GENERIC MAP ( TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (4, 0, 64, 9, 1, 0, 8, 17, 16), c_prefix, TRUE);
u4_rnd_3streams : ENTITY work.tb_fil_ppf_wide GENERIC MAP ( TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (4, 0, 64, 9, 3, 0, 8, 18, 16), c_prefix, TRUE);
u4_rnd_4channels : ENTITY work.tb_fil_ppf_wide GENERIC MAP ( TRUE, TRUE, (1, 1, 1, 1, 1, 1, 0), (4, 2, 64, 9, 3, 0, 8, 22, 16), c_prefix, TRUE);
END tb;
/trunk/tb_tb_fil_ppf_wide_file_data.vhd
0,0 → 1,101
--------------------------------------------------------------------------------
--
-- Copyright (C) 2016
-- 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/>.
--
--------------------------------------------------------------------------------
 
-- Purpose: Multi-testbench for fil_ppf_wide using file data
-- Description:
-- Verify fil_ppf_wide using coefficients and data generated by
-- Matlab $RADIOHDL_WORK/applications/apertif/matlab/run_pfir.m
--
-- Usage:
-- > as 4
-- > run -all
 
LIBRARY IEEE, common_pkg_lib;
USE IEEE.std_logic_1164.ALL;
USE common_pkg_lib.common_pkg.all;
USE work.fil_pkg.all;
 
ENTITY tb_tb_fil_ppf_wide_file_data IS
END tb_tb_fil_ppf_wide_file_data;
 
ARCHITECTURE tb OF tb_tb_fil_ppf_wide_file_data IS
CONSTANT c_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
CONSTANT c_coeff_prefix : string := "hex/run_pfir_m_pfir_coeff_fircls1";
CONSTANT c_data : string := "data/run_pfir_m_sinusoid_chirp_8b_16taps_128points_16b_16b.dat"; -- coefs, input and output data for 1 stream
CONSTANT c_data15 : string := "data/run_pfir_m_sinusoid_chirp_8b_15taps_128points_16b_16b.dat"; -- coefs, input and output data for 1 stream
SIGNAL tb_end : STD_LOGIC := '0'; -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
BEGIN
 
--g_big_endian_wb_in : boolean := true;
--g_big_endian_wb_out : boolean := true;
--g_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
-- -- type t_fil_pipeline is record
-- -- -- generic for the taps and coefficients memory
-- -- mem_delay : natural; -- = 2
-- -- -- generics for the multiplier in in the filter unit
-- -- mult_input : natural; -- = 1
-- -- mult_product : natural; -- = 1
-- -- mult_output : natural; -- = 1
-- -- -- generics for the adder tree in in the filter unit
-- -- adder_stage : natural; -- = 1
-- -- -- generics for the requantizer in the filter unit
-- -- requant_remove_lsb : natural; -- = 1
-- -- requant_remove_msb : natural; -- = 0
-- -- end record;
--g_fil_ppf : t_fil_ppf := (1, 1, 64, 8, 1, 8, 20, 16);
-- -- type t_fil_ppf is record
-- -- wb_factor : natural; -- = 1, the wideband factor
-- -- nof_chan : natural; -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan
-- -- nof_bands : natural; -- = 128, the number of polyphase channels (= number of points of the FFT)
-- -- nof_taps : natural; -- = 16, the number of FIR taps per subband
-- -- nof_streams : natural; -- = 1, the number of streams that are served by the same coefficients.
-- -- backoff_w : natural; -- = 0, number of bits for input backoff to avoid output overflow
-- -- in_dat_w : natural; -- = 8, number of input bits per stream
-- -- out_dat_w : natural; -- = 23, number of output bits (per stream). It is set to in_dat_w+coef_dat_w-1 = 23 to be sure the requantizer
-- -- does not remove any of the data in order to be able to verify with the original coefficients values.
-- -- coef_dat_w : natural; -- = 16, data width of the FIR coefficients
-- -- end record;
--g_coefs_file_prefix : string := "hex/run_pfir_m_pfir_coeff_fircls1";
--g_data_file : string := "data/run_pfir_m_sinusoid_chirp_8b_16taps_128points_16b_16b.dat"; -- coefs, input and output data for 1 stream
--g_data_file_nof_lines : natural := 25600; -- number of lines with input data that is available in the g_data_file
--g_data_file_nof_read : natural := 5000; -- number of lines with input data to read and simulate, must be <= g_data_file_nof_lines
--g_enable_in_val_gaps : boolean := FALSE
 
-- verify fil_ppf_wide for wb_factor=1, so effectively same as using fil_ppf_single directly
u1_act : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP (FALSE, FALSE, c_pipeline, (1, 0, 128, 16, 1, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 25600, FALSE);
u1_act_15taps : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP (FALSE, FALSE, c_pipeline, (1, 0, 128, 15, 1, 1, 8, 16, 16), c_coeff_prefix, c_data15, 25600, 5000, FALSE);
u1_rnd : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP (FALSE, FALSE, c_pipeline, (1, 0, 128, 16, 1, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 5000, TRUE);
u1_rnd_channels_streams : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP (FALSE, FALSE, c_pipeline, (1, 1, 128, 16, 2, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 5000, TRUE);
-- verify fil_ppf_wide for wb_factor>1 (be = big endian, le = little endian)
u4_act : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP ( TRUE, TRUE, c_pipeline, (4, 0, 128, 16, 1, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 25600, FALSE);
u4_act_be_le : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP ( TRUE, FALSE, c_pipeline, (4, 0, 128, 16, 1, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 25600, FALSE);
u4_act_le_be : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP (FALSE, TRUE, c_pipeline, (4, 0, 128, 16, 1, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 25600, FALSE);
u4_act_le_le : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP (FALSE, FALSE, c_pipeline, (4, 0, 128, 16, 1, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 25600, FALSE);
u4_act_15taps : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP ( TRUE, TRUE, c_pipeline, (4, 0, 128, 15, 1, 1, 8, 16, 16), c_coeff_prefix, c_data15, 25600, 5000, FALSE);
u4_rnd : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP ( TRUE, TRUE, c_pipeline, (4, 0, 128, 16, 1, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 5000, TRUE);
u4_rnd_channels_streams : ENTITY work.tb_fil_ppf_wide_file_data GENERIC MAP ( TRUE, TRUE, c_pipeline, (4, 1, 128, 16, 4, 1, 8, 16, 16), c_coeff_prefix, c_data, 25600, 5000, TRUE);
 
END tb;
/trunk/transcript
0,0 → 1,467
# // ModelSim SE-64 6.6c Aug 23 2010 Linux 4.15.0-112-generic
# //
# // Copyright 1991-2010 Mentor Graphics Corporation
# // All Rights Reserved.
# //
# // THIS WORK CONTAINS TRADE SECRET AND
# // PROPRIETARY INFORMATION WHICH IS THE PROPERTY
# // OF MENTOR GRAPHICS CORPORATION OR ITS LICENSORS
# // AND IS SUBJECT TO LICENSE TERMS.
# //
# do /home/schuur/OpenCores/radiohdl/modelsim/commands.do
# Loading general HDL library commands...
lp astron_filter
# Loading project astron_filter
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd failed with 2 errors.
# Compile of fil_ppf_ctrl.vhd failed with 2 errors.
# Compile of fil_ppf_filter.vhd failed with 2 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 2 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 2 errors.
# 11 compiles, 11 failed with 22 errors.
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd failed with 2 errors.
# Compile of fil_ppf_ctrl.vhd failed with 2 errors.
# Compile of fil_ppf_filter.vhd failed with 2 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 2 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 2 errors.
# 11 compiles, 11 failed with 22 errors.
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd failed with 2 errors.
# Compile of fil_ppf_ctrl.vhd failed with 2 errors.
# Compile of fil_ppf_filter.vhd failed with 2 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 2 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 2 errors.
# 11 compiles, 11 failed with 22 errors.
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd failed with 3 errors.
# Compile of fil_ppf_filter.vhd failed with 3 errors.
# Compile of fil_ppf_single.vhd failed with 3 errors.
# Compile of fil_ppf_wide.vhd failed with 3 errors.
# Compile of tb_fil_ppf_single.vhd failed with 3 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 3 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 3 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 3 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 3 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 3 errors.
# 11 compiles, 10 failed with 30 errors.
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd was successful.
# Compile of fil_ppf_filter.vhd failed with 3 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 4 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 1 errors.
# 11 compiles, 9 failed with 22 errors.
# astron_filter
lp astron_multiplier
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
# Loading project astron_multiplier
# astron_multiplier
ll
# ambiguous command name "ll": llength llookup
cd ..
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
lp astron_multiplier
# Loading project astron_multiplier
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of common_mult.vhd failed with 2 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 11 compiles, 3 failed with 5 errors.
# astron_multiplier
cd ..
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
lp astron_multiplier
# Loading project astron_multiplier
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of common_mult.vhd failed with 1 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 11 compiles, 3 failed with 4 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of common_mult.vhd failed with 1 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 11 compiles, 3 failed with 4 errors.
# astron_multiplier
cd ..
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
cd ..
lp astron_multiplier
# Loading project astron_multiplier
# astron_multiplier
mk copile
# Project directory copile not found
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd failed with 1 errors.
# Compile of common_mult.vhd failed with 1 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 12 compiles, 4 failed with 5 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd failed with 1 errors.
# Compile of common_mult.vhd failed with 1 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 12 compiles, 4 failed with 5 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd was successful.
# Compile of common_mult.vhd failed with 1 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 12 compiles, 3 failed with 4 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd was successful.
# Compile of common_mult.vhd failed with 2 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 12 compiles, 3 failed with 5 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd was successful.
# Compile of common_mult.vhd failed with 2 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 12 compiles, 3 failed with 5 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd was successful.
# Compile of common_mult.vhd failed with 2 errors.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 12 compiles, 3 failed with 5 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd was successful.
# Compile of common_mult.vhd was successful.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd failed with 1 errors.
# 12 compiles, 2 failed with 3 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd was successful.
# Compile of common_mult.vhd was successful.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd failed with 2 errors.
# Compile of tb_tb_common_mult.vhd was successful.
# 12 compiles, 1 failed with 2 errors.
# astron_multiplier
mk compile
# [mk compile astron_multiplier]
# Compile of altera_mf_components.vhd was successful.
# Compile of altera_mf.vhd was successful.
# Compile of ip_stratixiv_complex_mult.vhd was successful.
# Compile of ip_stratixiv_complex_mult_rtl.vhd was successful.
# Compile of tech_mult_component_pkg.vhd was successful.
# Compile of tech_complex_mult.vhd was successful.
# Compile of common_complex_mult.vhd was successful.
# Compile of tech_mult.vhd was successful.
# Compile of common_mult.vhd was successful.
# Compile of tb_common_complex_mult.vhd was successful.
# Compile of tb_common_mult.vhd was successful.
# Compile of tb_tb_common_mult.vhd was successful.
# 12 compiles, 0 failed with no errors.
# astron_multiplier
lp astron_filter
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
# Loading project astron_filter
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd was successful.
# Compile of fil_ppf_filter.vhd failed with 3 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 4 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 1 errors.
# 11 compiles, 9 failed with 22 errors.
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd was successful.
# Compile of fil_ppf_filter.vhd failed with 1 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 4 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 1 errors.
# 11 compiles, 9 failed with 20 errors.
# astron_filter
cd ..
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
lp astron_adder
# Loading project astron_adder
# astron_adder
mk compile
# [mk compile astron_adder]
# Compile of common_add_sub.vhd was successful.
# Compile of common_adder_tree.vhd was successful.
# Compile of common_adder_tree_a_str.vhd failed with 1 errors.
# Compile of tb_common_add_sub.vhd was successful.
# Compile of tb_tb_common_add_sub.vhd was successful.
# Compile of tb_common_adder_tree.vhd failed with 1 errors.
# Compile of tb_tb_common_adder_tree.vhd failed with 1 errors.
# 7 compiles, 3 failed with 3 errors.
# astron_adder
mk compile
# [mk compile astron_adder]
# Compile of common_add_sub.vhd was successful.
# Compile of common_adder_tree.vhd was successful.
# Compile of common_adder_tree_a_str.vhd was successful.
# Compile of tb_common_add_sub.vhd was successful.
# Compile of tb_tb_common_add_sub.vhd was successful.
# Compile of tb_common_adder_tree.vhd failed with 1 errors.
# Compile of tb_tb_common_adder_tree.vhd failed with 1 errors.
# 7 compiles, 2 failed with 2 errors.
# astron_adder
mk compile
# [mk compile astron_adder]
# Compile of common_add_sub.vhd was successful.
# Compile of common_adder_tree.vhd was successful.
# Compile of common_adder_tree_a_str.vhd was successful.
# Compile of tb_common_add_sub.vhd was successful.
# Compile of tb_tb_common_add_sub.vhd was successful.
# Compile of tb_common_adder_tree.vhd was successful.
# Compile of tb_tb_common_adder_tree.vhd was successful.
# 7 compiles, 0 failed with no errors.
# astron_adder
lp astron_filter
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
# Loading project astron_filter
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd was successful.
# Compile of fil_ppf_filter.vhd failed with 1 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 4 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 1 errors.
# 11 compiles, 9 failed with 20 errors.
# astron_filter
cd ..
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
 
lp astron_filter
# Loading project astron_filter
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd was successful.
# Compile of fil_ppf_filter.vhd failed with 2 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 4 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 1 errors.
# 11 compiles, 9 failed with 21 errors.
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd was successful.
# Compile of fil_ppf_filter.vhd failed with 2 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 4 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 1 errors.
# 11 compiles, 9 failed with 21 errors.
# astron_filter
cd ..
# reading /home/software/Mentor/6.6c/modeltech/linux_x86_64/../modelsim.ini
mk compile
lp astron_filter
# Loading project astron_filter
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd was successful.
# Compile of fil_ppf_filter.vhd failed with 2 errors.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 4 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 1 errors.
# 11 compiles, 9 failed with 21 errors.
# astron_filter
mk compile
# [mk compile astron_filter]
# Compile of fil_pkg.vhd was successful.
# Compile of fil_ppf_ctrl.vhd was successful.
# Compile of fil_ppf_filter.vhd was successful.
# Compile of fil_ppf_single.vhd failed with 2 errors.
# Compile of fil_ppf_wide.vhd failed with 2 errors.
# Compile of tb_fil_ppf_single.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide.vhd failed with 4 errors.
# Compile of tb_fil_ppf_wide_file_data.vhd failed with 4 errors.
# Compile of tb_tb_fil_ppf_single.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide.vhd failed with 1 errors.
# Compile of tb_tb_fil_ppf_wide_file_data.vhd failed with 1 errors.
# 11 compiles, 8 failed with 19 errors.
# astron_filter

powered by: WebSVN 2.1.0

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