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

Subversion Repositories astron_filter

[/] [astron_filter/] [trunk/] [tb_fil_ppf_wide.vhd] - Blame information for rev 2

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 2 danv
-- Author: Harm Jan Pepping : hajee at astron.nl   : April 2012
2
--         Eric Kooistra    : kooistra at astron.nl: july 2016
3
--------------------------------------------------------------------------------
4
--
5
-- Copyright (C) 2012
6
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
7
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
8
--
9
-- This program is free software: you can redistribute it and/or modify
10
-- it under the terms of the GNU General Public License as published by
11
-- the Free Software Foundation, either version 3 of the License, or
12
-- (at your option) any later version.
13
--
14
-- This program is distributed in the hope that it will be useful,
15
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
16
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17
-- GNU General Public License for more details.
18
--
19
-- You should have received a copy of the GNU General Public License
20
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.
21
--
22
--------------------------------------------------------------------------------
23
--
24
-- Purpose: Test bench for fil_ppf_wide.vhd
25
--
26
--   The DUT fil_ppf_wide.vhd has wb_factor >= 1 and uses array types and 
27
--   wb_factor instances of fil_ppf_single.vhd.
28
--
29
--   See also description tb_fil_ppf_single.vhd.
30
--
31
-- Usage:
32
--   > run -all
33
--   > testbench is selftesting. 
34
--
35
library ieee, common_pkg_lib, dp_pkg_lib, astron_diagnostics_lib, astron_ram_lib, astron_mm_lib;
36
use IEEE.std_logic_1164.all;
37
use IEEE.numeric_std.all;
38
use IEEE.std_logic_textio.all;
39
use std.textio.all;
40
use common_pkg_lib.common_pkg.all;
41
use astron_ram_lib.common_ram_pkg.ALL;
42
use common_pkg_lib.common_lfsr_sequences_pkg.ALL;
43
use common_pkg_lib.tb_common_pkg.all;
44
use astron_mm_lib.tb_common_mem_pkg.ALL;
45
use dp_pkg_lib.dp_stream_pkg.ALL;
46
use work.fil_pkg.all;
47
 
48
entity tb_fil_ppf_wide is
49
  generic(
50
    -- generics for tb
51
    g_big_endian_wb_in  : boolean := true;
52
    g_big_endian_wb_out : boolean := true;
53
    g_fil_ppf_pipeline : t_fil_ppf_pipeline := (1, 1, 1, 1, 1, 1, 0);
54
      -- type t_fil_pipeline is record
55
      --   -- generic for the taps and coefficients memory
56
      --   mem_delay      : natural;  -- = 2
57
      --   -- generics for the multiplier in in the filter unit
58
      --   mult_input     : natural;  -- = 1
59
      --   mult_product   : natural;  -- = 1
60
      --   mult_output    : natural;  -- = 1                   
61
      --   -- generics for the adder tree in in the filter unit
62
      --   adder_stage    : natural;  -- = 1
63
      --   -- generics for the requantizer in the filter unit
64
      --   requant_remove_lsb : natural;  -- = 1
65
      --   requant_remove_msb : natural;  -- = 0
66
      -- end record;
67
    g_fil_ppf : t_fil_ppf := (4, 1, 64, 8, 1, 0, 8, 23, 16);
68
      -- type t_fil_ppf is record
69
      --   wb_factor      : natural; -- = 4, the wideband factor
70
      --   nof_chan       : natural; -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan 
71
      --   nof_bands      : natural; -- = 1024, the number of polyphase channels (= number of points of the FFT)
72
      --   nof_taps       : natural; -- = 16, the number of FIR taps per subband
73
      --   nof_streams    : natural; -- = 1, the number of streams that are served by the same coefficients. 
74
      --   backoff_w      : natural; -- = 0, number of bits for input backoff to avoid output overflow
75
      --   in_dat_w       : natural; -- = 8, number of input bits per stream
76
      --   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
77
      --                                  does not remove any of the data in order to be able to verify with the original coefficients values. 
78
      --   coef_dat_w     : natural; -- = 16, data width of the FIR coefficients
79
      -- end record;
80
    g_coefs_file_prefix  : string  := "hex/run_pfir_coeff_m_incrementing";
81
    g_enable_in_val_gaps : boolean := FALSE
82
  );
83
end entity tb_fil_ppf_wide;
84
 
85
architecture tb of tb_fil_ppf_wide is
86
 
87
  constant c_clk_period : time    := 10 ns;
88
 
89
  constant c_nof_channels        : natural := 2**g_fil_ppf.nof_chan;
90
  constant c_nof_coefs           : natural := g_fil_ppf.nof_taps * g_fil_ppf.nof_bands;       -- nof PFIR coef
91
  constant c_nof_coefs_per_wb    : natural := c_nof_coefs / g_fil_ppf.wb_factor;
92
  constant c_nof_data_in_filter  : natural := c_nof_coefs * c_nof_channels;                   -- nof PFIR coef expanded for all channels
93
  constant c_nof_data_per_tap    : natural := c_nof_data_in_filter / g_fil_ppf.nof_taps;
94
  constant c_nof_valid_in_filter : natural := c_nof_data_in_filter / g_fil_ppf.wb_factor;
95
  constant c_nof_valid_per_tap   : natural := c_nof_data_per_tap / g_fil_ppf.wb_factor;
96
  constant c_nof_bands_per_mif   : natural := g_fil_ppf.nof_bands / g_fil_ppf.wb_factor;
97
  constant c_mif_coef_mem_addr_w : natural := ceil_log2(g_fil_ppf.nof_bands);
98
  constant c_mif_coef_mem_span   : natural := 2**c_mif_coef_mem_addr_w;                       -- mif coef mem span for one tap
99
 
100
  constant c_coefs_file_prefix   : string  := g_coefs_file_prefix & "_" & integer'image(g_fil_ppf.nof_taps) & "taps" &
101
                                                                    "_" & integer'image(g_fil_ppf.nof_bands) & "points" &
102
                                                                    "_" & integer'image(g_fil_ppf.coef_dat_w) & "b";
103
  constant c_mif_file_prefix     : string  := c_coefs_file_prefix & "_" & integer'image(g_fil_ppf.wb_factor) & "wb";
104
 
105
  constant c_fil_prod_w          : natural := g_fil_ppf.in_dat_w + g_fil_ppf.coef_dat_w - 1;  -- skip double sign bit
106
  constant c_fil_sum_w           : natural := c_fil_prod_w;                                   -- DC gain = 1
107
  constant c_fil_lsb_w           : natural := c_fil_sum_w - g_fil_ppf.out_dat_w;              -- nof LSbits that get rounded for out_dat
108
  constant c_in_ampl             : natural := 2**c_fil_lsb_w;                                 -- scale in_dat to compensate for rounding
109
 
110
  constant c_gap_factor          : natural := sel_a_b(g_enable_in_val_gaps, 3, 1);
111
 
112
  -- input/output data width
113
  constant c_in_dat_w            : natural := g_fil_ppf.in_dat_w;
114
  constant c_out_dat_w           : natural := g_fil_ppf.out_dat_w;
115
 
116
  type t_wb_integer_arr2 is array(integer range <>) of t_integer_arr(c_nof_valid_in_filter-1 downto 0);
117
 
118
  -- signal definitions
119
  signal tb_end         : std_logic := '0';
120
  signal tb_end_mm      : std_logic := '0';
121
  signal tb_end_almost  : std_logic := '0';
122
  signal clk            : std_logic := '0';
123
  signal rst            : std_logic := '0';
124
  signal random         : std_logic_vector(15 DOWNTO 0) := (OTHERS=>'0');  -- use different lengths to have different random sequences
125
 
126
  signal ram_coefs_mosi : t_mem_mosi := c_mem_mosi_rst;
127
  signal ram_coefs_miso : t_mem_miso;
128
 
129
  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
130
  signal in_val          : std_logic;
131
  signal in_val_cnt      : natural := 0;
132
  signal in_gap          : std_logic := '0';
133
 
134
  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
135
  signal out_val         : std_logic;
136
  signal out_val_cnt     : natural := 0;
137
 
138
  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
139
  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
140
 
141
  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
142
  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
143
  signal ref_dat_arr     : t_integer_arr(0 to g_fil_ppf.wb_factor-1) := (OTHERS=>0);
144
 
145
  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           
146
 
147
begin
148
 
149
  clk <= (not clk) or tb_end after c_clk_period/2;
150
  rst <= '1', '0' after c_clk_period*7;
151
  random <= func_common_random(random) WHEN rising_edge(clk);
152
  in_gap <= random(random'HIGH) WHEN g_enable_in_val_gaps=TRUE ELSE '0';
153
 
154
  ---------------------------------------------------------------
155
  -- SEND IMPULSE TO THE DATA INPUT
156
  ---------------------------------------------------------------  
157
  p_send_impulse : process
158
  begin
159
    tb_end <= '0';
160
    in_dat_arr <= (others=>(others=>'0'));
161
    in_val <= '0';
162
    proc_common_wait_until_low(clk, rst);         -- Wait until reset has finished
163
    proc_common_wait_some_cycles(clk, 10);        -- Wait an additional amount of cycles
164
 
165
    -- 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
166
 
167
    -- Pulse during first tap of all channels
168
    for I in 0 to c_nof_valid_per_tap-1 loop
169
      for P in 0 to g_fil_ppf.wb_factor-1 loop
170
        for S in 0 to g_fil_ppf.nof_streams-1 loop
171
          in_dat_arr(P*g_fil_ppf.nof_streams + S) <= TO_UVEC(c_in_ampl, c_fil_slv_w);
172
          in_val                                  <= '1';
173
        end loop;
174
      end loop;
175
      in_val <= '1';
176
      proc_common_wait_some_cycles(clk, 1);
177
      if in_gap='1' then
178
        in_val <= '0';
179
        proc_common_wait_some_cycles(clk, 1);
180
      end if;
181
    end loop;
182
 
183
    -- 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
184
    in_dat_arr <= (others=>(others=>'0'));
185
    FOR J IN 0 TO g_fil_ppf.nof_taps-2 +1 +1  LOOP
186
      FOR I IN 0 TO c_nof_valid_per_tap-1 LOOP
187
        in_val <= '1';
188
        proc_common_wait_some_cycles(clk, 1);
189
        IF in_gap='1' THEN
190
          in_val <= '0';
191
          proc_common_wait_some_cycles(clk, 1);
192
        END IF;
193
      END LOOP;
194
    END LOOP;
195
    in_val <= '0';
196
 
197
    -- Wait until done
198
    proc_common_wait_some_cycles(clk, c_gap_factor*c_nof_valid_per_tap);  -- PPF latency of 1 tap
199
    proc_common_wait_until_high(clk, tb_end_mm);                          -- MM read done
200
    tb_end_almost <= '1';
201
    proc_common_wait_some_cycles(clk, 10);
202
    tb_end <= '1';
203
    WAIT;
204
  END PROCESS;
205
 
206
  ---------------------------------------------------------------  
207
  -- CREATE REFERENCE ARRAY
208
  ---------------------------------------------------------------  
209
  p_create_ref_from_coefs_file : PROCESS
210
    variable v_coefs_flip_arr : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0);
211
  begin
212
    -- Read all coeffs from coefs file
213
    proc_common_read_integer_file(c_coefs_file_prefix & ".dat", 0, c_nof_coefs, 1, ref_coefs_arr);
214
    wait for 1 ns;
215
    -- Reverse the coeffs per tap
216
    for J in 0 to g_fil_ppf.nof_taps-1 loop
217
      for I in 0 to g_fil_ppf.nof_bands-1 loop
218
        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);
219
      end loop;
220
    end loop;
221
    -- Distribute over wb_factor and expand the channels (for one stream)
222
    for I in 0 to c_nof_coefs_per_wb-1 loop
223
      for P in 0 to g_fil_ppf.wb_factor-1 loop
224
        for K in 0 to c_nof_channels-1 loop
225
          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));
226
        end loop;
227
      end loop;
228
    end loop;
229
    wait;
230
  end process;
231
 
232
  p_create_ref_from_mif_file : PROCESS
233
  begin
234
    for P in 0 to g_fil_ppf.wb_factor-1 loop
235
      for J in 0 to g_fil_ppf.nof_taps-1 loop
236
        -- Read coeffs per wb and per tap from MIF file
237
        proc_common_read_mif_file(c_mif_file_prefix & "_" & integer'image(P*g_fil_ppf.nof_taps+J) & ".mif", mif_coefs_arr);
238
        wait for 1 ns;
239
        -- Expand the channels (for one stream)
240
        for I in 0 to c_nof_bands_per_mif-1 loop
241
          for K in 0 to c_nof_channels-1 loop
242
            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));
243
          end loop;
244
        end loop;
245
      end loop;
246
    end loop;
247
    wait;
248
  end process;
249
 
250
  p_coefs_memory_read : process
251
    variable v_mif_index   : natural;
252
    variable v_mif_base    : natural;
253
    variable v_coef_offset : natural;
254
    variable v_coef_index  : natural;
255
  begin
256
    ram_coefs_mosi <= c_mem_mosi_rst;
257
    for P in 0 to g_fil_ppf.wb_factor-1 loop
258
      for J in 0 to g_fil_ppf.nof_taps-1 loop
259
        v_mif_index := P*g_fil_ppf.nof_taps+J;
260
        v_mif_base  := v_mif_index*c_mif_coef_mem_span;
261
        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
262
        for I in 0 to c_nof_bands_per_mif-1 loop
263
          proc_mem_mm_bus_rd(v_mif_base+I, clk, ram_coefs_miso, ram_coefs_mosi);
264
          proc_mem_mm_bus_rd_latency(1, clk);
265
          v_coef_index := v_coef_offset - I*g_fil_ppf.wb_factor;
266
          read_coefs_arr(v_coef_index) <= TO_SINT(ram_coefs_miso.rddata(g_fil_ppf.coef_dat_w-1 DOWNTO 0));
267
        end loop;
268
      end loop;
269
    end loop;
270
    proc_common_wait_some_cycles(clk, 1);
271
    tb_end_mm <= '1';
272
    wait;
273
  end process;
274
 
275
  ---------------------------------------------------------------  
276
  -- DUT = Device Under Test
277
  ---------------------------------------------------------------  
278
  u_dut : entity work.fil_ppf_wide
279
  generic map (
280
    g_big_endian_wb_in  => g_big_endian_wb_in,
281
    g_big_endian_wb_out => g_big_endian_wb_out,
282
    g_fil_ppf           => g_fil_ppf,
283
    g_fil_ppf_pipeline  => g_fil_ppf_pipeline,
284
    g_coefs_file_prefix => c_mif_file_prefix
285
  )
286
  port map (
287
    dp_clk         => clk,
288
    dp_rst         => rst,
289
    mm_clk         => clk,
290
    mm_rst         => rst,
291
    ram_coefs_mosi => ram_coefs_mosi,
292
    ram_coefs_miso => ram_coefs_miso,
293
    in_dat_arr     => in_dat_arr,
294
    in_val         => in_val,
295
    out_dat_arr    => out_dat_arr,
296
    out_val        => out_val
297
  );
298
 
299
  -- Verify the output of the DUT with the expected output from the reference array
300
  p_verify_out_dat_width : process
301
  begin
302
    -- Wait until tb_end_almost to avoid that the Error message gets lost in earlier messages
303
    proc_common_wait_until_high(clk, tb_end_almost);
304
    assert g_fil_ppf.out_dat_w >= g_fil_ppf.coef_dat_w report "Output data width too small for coefficients" severity error;
305
    wait;
306
  end process;
307
 
308
  p_verify_out_val_cnt : process
309
  begin
310
    -- Wait until tb_end_almost
311
    proc_common_wait_until_high(clk, tb_end_almost);
312
    -- The filter has a latency of 1 tap, so there remains in_dat for tap in the filter
313
    assert in_val_cnt > 0                               report "Test did not run, no valid input data" severity error;
314
    assert out_val_cnt = in_val_cnt-c_nof_valid_per_tap report "Unexpected number of valid output data coefficients" severity error;
315
    wait;
316
  end process;
317
 
318
  in_val_cnt  <= in_val_cnt+1  when rising_edge(clk) and in_val='1'  else in_val_cnt;
319
  out_val_cnt <= out_val_cnt+1 when rising_edge(clk) and out_val='1' else out_val_cnt;
320
 
321
  gen_ref_dat_arr : for P in 0 to g_fil_ppf.wb_factor-1 generate
322
    ref_dat_arr(P) <= ref_dat_arr2(P)(out_val_cnt) when out_val_cnt < c_nof_valid_in_filter else 0;
323
  end generate;
324
 
325
  p_verify_out_dat : process(clk)
326
    variable v_coeff : integer;
327
    variable vP      : natural;
328
  begin
329
    if rising_edge(clk) then
330
      if out_val='1' then
331
        for P in 0 to g_fil_ppf.wb_factor-1 loop
332
          -- Adjust index for v_coeff dependend on g_big_endian_wb_out over all wb and streams for out_dat_arr,
333
          -- because ref_dat_arr for 1 stream uses little endian time [0,1,2,3] to P [0,1,2,3] index mapping
334
          if g_big_endian_wb_out=false then
335
            vP := P;
336
          else
337
            vP := g_fil_ppf.wb_factor-1-P;
338
          end if;
339
 
340
          -- Output data width must be large enough to fit the coefficients width, this is verified by p_verify_out_dat_width
341
          -- 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)
342
          -- wraps to -2**(w-1), so then compensate for that here.
343
          if g_fil_ppf.out_dat_w > g_fil_ppf.coef_dat_w then
344
            v_coeff :=  ref_dat_arr(vP);  -- positive input pulse
345
          else
346
            v_coeff := -ref_dat_arr(vP);  -- compensate for full scale negative input pulse
347
          end if;
348
          for S in 0 to g_fil_ppf.nof_streams-1 loop
349
            -- all streams carry the same data
350
            assert TO_SINT(out_dat_arr(P*g_fil_ppf.nof_streams + S)) = v_coeff report "Output data error" severity error;
351
          end loop;
352
        end loop;
353
      end if;
354
    end if;
355
  end process;
356
 
357
end tb;

powered by: WebSVN 2.1.0

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