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

Subversion Repositories astron_multiplexer

[/] [astron_multiplexer/] [trunk/] [dp_mux.vhd] - Blame information for rev 2

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 2 danv
--------------------------------------------------------------------------------
2
--
3
-- Copyright (C) 2010
4
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
5
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
6
--
7
-- This program is free software: you can redistribute it and/or modify
8
-- it under the terms of the GNU General Public License as published by
9
-- the Free Software Foundation, either version 3 of the License, or
10
-- (at your option) any later version.
11
--
12
-- This program is distributed in the hope that it will be useful,
13
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
14
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15
-- GNU General Public License for more details.
16
--
17
-- You should have received a copy of the GNU General Public License
18
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.
19
--
20
--------------------------------------------------------------------------------
21
 
22
-- Purpose:
23
--   Multiplex frames from one or more input streams into one output stream.
24
-- Description:
25
--   The frames are marked by sop and eop. The input selection scheme depends
26
--   on g_mode:
27
--   0: Framed round-robin with fair chance.
28
--      Uses eop to select next input after the frame has been passed on or
29
--      select the next input when there is no frame coming in on the current
30
--      input, so it has had its chance.
31
--   1: Framed round-robin in forced order from each input.
32
--      Uses eop to select next output. Holds input selection until sop is
33
--      detected on that input. Results in ordered (low to high) but blocking
34
--      (on absence of sop) input selection.
35
--   2: Unframed external MM control input to select the output.
36
--      Three options have been considered for the flow control:
37
--      a) Use src_in for all inputs, data from the not selected inputs
38
--         will get lost. In case FIFOs are used they are only useful used for
39
--         the selected input.
40
--      b) Use c_dp_siso_rdy for unused inputs, this flushes them like with
41
--         option a) but possibly even faster in case the src_in.ready may get
42
--         inactive to apply backpressure.
43
--      c) Use c_dp_siso_hold for unused inputs, to stop them until they get
44
--         selected again.
45
--      Support only option a) because assume that the sel_ctrl is rather 
46
--      static and the data from the unused inputs can be ignored.
47
--   3: Framed external sel_ctrl input to select the output.
48
--      This scheme is identical to g_mode=0, but with xon='1' only for the 
49
--      selected input. The other not selected inputs have xon='0', so they
50
--      will stop getting input frames and the round-robin scheme of g_mode=0
51
--      will then automatically select only remaining active input.
52
--      The assumption is that the upstream input sources do stop their output
53
--      after they finished the current frame when xon='0'. If necessary
54
--      dp_xonoff could be used to add such frame flow control to an input
55
--      stream that does not yet support xon/xoff. But better use g_mode=4 
56
--      instead of g_mode=3, because the implementation of g_mode=4 is more
57
--      simple.
58
--   4) Framed external sel_ctrl input to select the output without ready.
59
--      This is preferred over g_mode=3 because it passes on the ready but
60
--      does not use it self. Not selected inputs have xon='0'. Only the
61
--      selected input has xon='1'. When sel_ctrl changes then briefly all
62
--      inputs get xon='0'. The new selected input only gets xon='1' when
63
--      the current selected input is idle or has become idle.
64
--       
65
--   The low part of the src_out.channel has c_sel_w = log2(g_nof_input) nof
66
--   bits and equals the input port number. The snk_in_arr().channel bits are
67
--   copied into the high part of the src_out.channel. Hence the total
68
--   effective output channel width becomes g_in_channel_w+c_sel_w when
69
--   g_use_in_channel=TRUE else c_sel_w.
70
--   If g_use_fifo=TRUE then the frames are buffered at the input, else the
71
--   connecting inputs need to take care of that.
72
-- Remark:
73
-- . Using g_nof_input=1 is transparent.
74
-- . Difference with dp_frame_scheduler is that dp_frame_scheduler does not
75
--   support back pressure via the ready signals.
76
-- . This dp_mux adds true_log2(nof ports) low bits to out_channel and the
77
--   dp_demux removes true_log2(nof ports) low bits from in_channel.
78
-- . For multiplexing time series frames or sample it can be applicable to
79
--   use g_append_channel_lo=FALSE in combination with g_mode=2.
80
 
81
LIBRARY IEEE, common_pkg_lib, dp_pkg_lib, dp_components_lib, dp_fifo_lib, technology_lib;
82
USE IEEE.std_logic_1164.ALL;
83
USE IEEE.numeric_std.ALL;
84
USE common_pkg_lib.common_pkg.ALL;
85
USE dp_pkg_lib.dp_stream_pkg.ALL;
86
USE technology_lib.technology_select_pkg.ALL;
87
 
88
ENTITY dp_mux IS
89
  GENERIC (
90
    g_technology        : NATURAL := c_tech_select_default;
91
    -- MUX
92
    g_mode              : NATURAL := 0;
93
    g_nof_input         : NATURAL := 2;                   -- >= 1
94
    g_append_channel_lo : BOOLEAN := TRUE;
95
    g_sel_ctrl_invert   : BOOLEAN := FALSE;  -- Use default FALSE when stream array IO are indexed (0 TO g_nof_input-1), else use TRUE when indexed (g_nof_input-1 DOWNTO 0)
96
    -- Input FIFO
97
    g_use_fifo          : BOOLEAN := FALSE;
98
    g_bsn_w             : NATURAL := 16;
99
    g_data_w            : NATURAL := 16;
100
    g_empty_w           : NATURAL := 1;
101
    g_in_channel_w      : NATURAL := 1;
102
    g_error_w           : NATURAL := 1;
103
    g_use_bsn           : BOOLEAN := FALSE;
104
    g_use_empty         : BOOLEAN := FALSE;
105
    g_use_in_channel    : BOOLEAN := FALSE;
106
    g_use_error         : BOOLEAN := FALSE;
107
    g_use_sync          : BOOLEAN := FALSE;
108
    g_fifo_af_margin    : NATURAL := 4;  -- Nof words below max (full) at which fifo is considered almost full
109
    g_fifo_size         : t_natural_arr := array_init(1024, 2);  -- must match g_nof_input, even when g_use_fifo=FALSE
110
    g_fifo_fill         : t_natural_arr := array_init(   0, 2)   -- must match g_nof_input, even when g_use_fifo=FALSE
111
  );
112
  PORT (
113
    rst         : IN  STD_LOGIC;
114
    clk         : IN  STD_LOGIC;
115
    -- Control
116
    sel_ctrl    : IN  NATURAL RANGE 0 TO g_nof_input-1 := 0;  -- used by g_mode = 2, 3, 4
117
    -- ST sinks
118
    snk_out_arr : OUT t_dp_siso_arr(0 TO g_nof_input-1);
119
    snk_in_arr  : IN  t_dp_sosi_arr(0 TO g_nof_input-1);
120
    -- ST source
121
    src_in      : IN  t_dp_siso;
122
    src_out     : OUT t_dp_sosi
123
  );
124
END dp_mux;
125
 
126
 
127
ARCHITECTURE rtl OF dp_mux IS
128
 
129
  -- Convert unconstrained range (that starts at INTEGER'LEFT) to 0 TO g_nof_input-1 range
130
  CONSTANT c_fifo_fill  : t_natural_arr(0 TO g_nof_input-1) := g_fifo_fill;
131
  CONSTANT c_fifo_size  : t_natural_arr(0 TO g_nof_input-1) := g_fifo_size;
132
 
133
  -- The low part of src_out.channel is used to represent the input port and the high part of src_out.channel is copied from snk_in_arr().channel
134
  CONSTANT c_sel_w      : NATURAL := true_log2(g_nof_input);
135
 
136
  CONSTANT c_rl         : NATURAL := 1;
137
  SIGNAL tb_ready_reg   : STD_LOGIC_VECTOR(0 TO g_nof_input*(1+c_rl)-1);
138
 
139
  TYPE state_type IS (s_idle, s_output);
140
 
141
  SIGNAL state            : state_type;
142
  SIGNAL nxt_state        : state_type;
143
 
144
  SIGNAL i_snk_out_arr    : t_dp_siso_arr(0 TO g_nof_input-1);
145
 
146
  SIGNAL sel_ctrl_reg     : NATURAL RANGE 0 TO g_nof_input-1;
147
  SIGNAL nxt_sel_ctrl_reg : NATURAL;
148
  SIGNAL sel_ctrl_evt     : STD_LOGIC;
149
  SIGNAL nxt_sel_ctrl_evt : STD_LOGIC;
150
 
151
  SIGNAL in_sel           : NATURAL RANGE 0 TO g_nof_input-1;  -- input port low part of src_out.channel
152
  SIGNAL nxt_in_sel       : NATURAL;
153
  SIGNAL next_sel         : NATURAL;
154
 
155
  SIGNAL rd_siso_arr      : t_dp_siso_arr(0 TO g_nof_input-1);
156
  SIGNAL rd_sosi_arr      : t_dp_sosi_arr(0 TO g_nof_input-1);
157
  SIGNAL rd_sosi_busy_arr : STD_LOGIC_VECTOR(0 TO g_nof_input-1);
158
 
159
  SIGNAL hold_src_in_arr  : t_dp_siso_arr(0 TO g_nof_input-1);
160
  SIGNAL next_src_out_arr : t_dp_sosi_arr(0 TO g_nof_input-1);
161
  SIGNAL pend_src_out_arr : t_dp_sosi_arr(0 TO g_nof_input-1);  -- SOSI control
162
 
163
  SIGNAL in_xon_arr       : STD_LOGIC_VECTOR(0 TO g_nof_input-1);
164
  SIGNAL nxt_in_xon_arr   : STD_LOGIC_VECTOR(0 TO g_nof_input-1);
165
 
166
  SIGNAL prev_src_in      : t_dp_siso;
167
  SIGNAL src_out_hi       : t_dp_sosi;  -- snk_in_arr().channel as high part of src_out.channel
168
  SIGNAL nxt_src_out_hi   : t_dp_sosi;
169
  SIGNAL channel_lo       : STD_LOGIC_VECTOR(c_sel_w-1 DOWNTO 0);
170
  SIGNAL nxt_channel_lo   : STD_LOGIC_VECTOR(c_sel_w-1 DOWNTO 0);
171
 
172
BEGIN
173
 
174
  snk_out_arr <= i_snk_out_arr;
175
 
176
  -- Monitor sink valid input and sink ready output
177
  proc_dp_siso_alert(clk, snk_in_arr, i_snk_out_arr, tb_ready_reg);
178
 
179
  p_src_out_wires : PROCESS(src_out_hi, channel_lo)
180
  BEGIN
181
    -- SOSI
182
    src_out <= src_out_hi;
183
 
184
    IF g_append_channel_lo=TRUE THEN
185
      -- The high part of src_out.channel copies the snk_in_arr().channel, the low part of src_out.channel is used to indicate the input port
186
      src_out.channel                     <= SHIFT_UVEC(src_out_hi.channel, -c_sel_w);
187
      src_out.channel(c_sel_w-1 DOWNTO 0) <= channel_lo;
188
    END IF;
189
  END PROCESS;
190
 
191
  p_clk: PROCESS(clk, rst)
192
  BEGIN
193
    IF rst='1' THEN
194
      sel_ctrl_reg <= 0;
195
      sel_ctrl_evt <= '0';
196
      in_xon_arr   <= (OTHERS=>'0');
197
      in_sel       <= 0;
198
      prev_src_in  <= c_dp_siso_rst;
199
      state        <= s_idle;
200
      src_out_hi   <= c_dp_sosi_rst;
201
      channel_lo   <= (OTHERS=>'0');
202
    ELSIF rising_edge(clk) THEN
203
      sel_ctrl_reg <= nxt_sel_ctrl_reg;
204
      sel_ctrl_evt <= nxt_sel_ctrl_evt;
205
      in_xon_arr   <= nxt_in_xon_arr;
206
      in_sel       <= nxt_in_sel;
207
      prev_src_in  <= src_in;
208
      state        <= nxt_state;
209
      src_out_hi   <= nxt_src_out_hi;
210
      channel_lo   <= nxt_channel_lo;
211
    END IF;
212
  END PROCESS;
213
 
214
  gen_input : FOR I IN 0 TO g_nof_input-1 GENERATE
215
    gen_fifo : IF g_use_fifo=TRUE GENERATE
216
      u_fill : ENTITY dp_fifo_lib.dp_fifo_fill
217
      GENERIC MAP (
218
        g_technology     => g_technology,
219
        g_bsn_w          => g_bsn_w,
220
        g_data_w         => g_data_w,
221
        g_empty_w        => g_empty_w,
222
        g_channel_w      => g_in_channel_w,
223
        g_error_w        => g_error_w,
224
        g_use_bsn        => g_use_bsn,
225
        g_use_empty      => g_use_empty,
226
        g_use_channel    => g_use_in_channel,
227
        g_use_error      => g_use_error,
228
        g_use_sync       => g_use_sync,
229
        g_fifo_fill      => c_fifo_fill(I),
230
        g_fifo_size      => c_fifo_size(I),
231
        g_fifo_af_margin => g_fifo_af_margin,
232
        g_fifo_rl        => 1
233
      )
234
      PORT MAP (
235
        rst      => rst,
236
        clk      => clk,
237
        -- ST sink
238
        snk_out  => i_snk_out_arr(I),
239
        snk_in   => snk_in_arr(I),
240
        -- ST source
241
        src_in   => rd_siso_arr(I),
242
        src_out  => rd_sosi_arr(I)
243
      );
244
    END GENERATE;
245
    no_fifo : IF g_use_fifo=FALSE GENERATE
246
      i_snk_out_arr <= rd_siso_arr;
247
      rd_sosi_arr   <= snk_in_arr;
248
    END GENERATE;
249
 
250
    -- Hold the sink input to be able to register the source output
251
    u_hold : ENTITY dp_components_lib.dp_hold_input
252
    PORT MAP (
253
      rst          => rst,
254
      clk          => clk,
255
      -- ST sink
256
      snk_out      => OPEN,                 -- SISO ready
257
      snk_in       => rd_sosi_arr(I),       -- SOSI
258
      -- ST source
259
      src_in       => hold_src_in_arr(I),   -- SISO ready
260
      next_src_out => next_src_out_arr(I),  -- SOSI
261
      pend_src_out => pend_src_out_arr(I),
262
      src_out_reg  => src_out_hi
263
    );
264
  END GENERATE;
265
 
266
  -- Register and adjust external MM sel_ctrl for g_sel_ctrl_invert
267
  nxt_sel_ctrl_reg <= sel_ctrl WHEN g_sel_ctrl_invert=FALSE ELSE g_nof_input-1-sel_ctrl;
268
 
269
  -- Detect change in sel_ctrl
270
  nxt_sel_ctrl_evt <= '1' WHEN nxt_sel_ctrl_reg/=sel_ctrl_reg ELSE '0';
271
 
272
  -- The output register stage matches RL = 1 for src_in.ready
273
  nxt_src_out_hi <= next_src_out_arr(in_sel);  -- default output selected next_src_out_arr 
274
  nxt_channel_lo <= TO_UVEC(in_sel, c_sel_w);  -- pass on input index via channel low
275
 
276
  ------------------------------------------------------------------------------
277
  -- Unframed MM controlled input selection scheme
278
  ------------------------------------------------------------------------------
279
 
280
  gen_sel_ctrl_direct : IF g_mode=2 GENERATE
281
    hold_src_in_arr <= (OTHERS=>src_in);  -- pass src_in on to all inputs, only the selected input sosi gets used and the sosi from the other inputs will get lost
282
    rd_siso_arr     <= (OTHERS=>src_in);
283
 
284
    nxt_in_sel <= sel_ctrl_reg;  -- external MM control selects the input
285
  END GENERATE;
286
 
287
  ------------------------------------------------------------------------------
288
  -- Framed input selection schemes
289
  ------------------------------------------------------------------------------
290
 
291
  gen_sel_ctrl_framed : IF g_mode=4 GENERATE
292
    u_dp_frame_busy_arr : ENTITY work.dp_frame_busy_arr
293
    GENERIC MAP (
294
      g_nof_inputs => g_nof_input,
295
      g_pipeline   => 1   -- register snk_in_busy to ease timing closure
296
    )
297
    PORT MAP (
298
      rst             => rst,
299
      clk             => clk,
300
      snk_in_arr      => rd_sosi_arr,
301
      snk_in_busy_arr => rd_sosi_busy_arr
302
    );
303
 
304
    hold_src_in_arr <= (OTHERS=>c_dp_siso_rdy);  -- effectively bypass the dp_hold_input
305
 
306
    p_rd_siso_arr : PROCESS(src_in, in_xon_arr)
307
    BEGIN
308
      FOR I IN 0 TO g_nof_input-1 LOOP
309
        rd_siso_arr(I).ready <= src_in.ready;    -- default pass on src_in ready flow control to all inputs
310
        rd_siso_arr(I).xon   <= in_xon_arr(I);   -- use xon to enable one input and stop all other inputs
311
      END LOOP;
312
    END PROCESS;
313
 
314
    p_state : PROCESS(state, in_sel, rd_sosi_busy_arr, sel_ctrl_reg, sel_ctrl_evt)
315
    BEGIN
316
      nxt_state      <= state;
317
      nxt_in_sel     <= in_sel;
318
      nxt_in_xon_arr <= (OTHERS=>'0');  -- Default stop all inputs
319
 
320
      CASE state IS
321
        WHEN s_idle =>
322
          -- Wait until all inputs are inactive (due to xon='0') to ensure that the old input has finished its last frame and the new input has not started yet
323
          IF UNSIGNED(rd_sosi_busy_arr)=0 THEN
324
            nxt_in_sel <= sel_ctrl_reg;
325
            nxt_state <= s_output;
326
          END IF;
327
 
328
        WHEN OTHERS => -- s_output
329
          -- Enable only the selected input via xon='1'
330
          nxt_in_xon_arr(sel_ctrl_reg) <= '1';
331
 
332
          -- Detect if the input selection changes
333
          IF sel_ctrl_evt='1' THEN
334
            nxt_state <= s_idle;
335
          END IF;
336
      END CASE;
337
    END PROCESS;
338
  END GENERATE;
339
 
340
 
341
  gen_framed : IF g_mode=0 OR g_mode=1 OR g_mode=3 GENERATE
342
    p_hold_src_in_arr : PROCESS(rd_siso_arr, pend_src_out_arr, in_sel, src_in)
343
    BEGIN
344
      hold_src_in_arr <= rd_siso_arr;       -- default ready for hold input when ready for sink input
345
      IF pend_src_out_arr(in_sel).eop='1' THEN
346
        hold_src_in_arr(in_sel) <= src_in;  -- also ready for hold input when the eop is there
347
      END IF;
348
    END PROCESS;
349
 
350
    next_sel <= in_sel+1 WHEN in_sel<g_nof_input-1 ELSE 0;
351
 
352
    p_state : PROCESS(state, in_sel, next_sel, pend_src_out_arr, src_in, prev_src_in, sel_ctrl_reg)
353
    BEGIN
354
      rd_siso_arr <= (OTHERS=>c_dp_siso_hold);  -- default not ready for input, but xon='1'
355
 
356
      nxt_in_sel <= in_sel;
357
 
358
      nxt_state <= state;
359
 
360
      CASE state IS
361
        WHEN s_idle =>
362
          -- Need to check pend_src_out_arr(in_sel).sop, which can be active if prev_src_in.ready was '1',
363
          -- because src_in.ready may be '0' and then next_src_out_arr(in_sel).sop is '0'
364
          IF pend_src_out_arr(in_sel).sop='1' THEN
365
            IF pend_src_out_arr(in_sel).eop='1' THEN
366
              rd_siso_arr <= (OTHERS=>c_dp_siso_hold);  -- the sop and the eop are there, it is a frame with only one data word, stop reading this input
367
              IF src_in.ready='1' THEN
368
                nxt_in_sel            <= next_sel;      -- the pend_src_out_arr(in_sel).eop will be output, so continue to next input.
369
                rd_siso_arr(next_sel) <= src_in;
370
              END IF;
371
            ELSE
372
              rd_siso_arr(in_sel) <= src_in;            -- the sop is there, so start outputting the frame from this input
373
              nxt_state <= s_output;
374
            END IF;
375
          ELSE
376
            CASE g_mode IS
377
              WHEN 0 | 3 =>
378
                -- Framed round-robin with fair chance per input
379
                IF prev_src_in.ready='0' THEN
380
                  rd_siso_arr(in_sel) <= src_in;        -- no sop, remain at current input to give it a chance
381
                ELSE
382
                  nxt_in_sel            <= next_sel;    -- no sop, select next input, because the current input has had a chance
383
                  rd_siso_arr(next_sel) <= src_in;
384
                END IF;
385
              WHEN OTHERS =>  -- = 1
386
                -- Framed round-robin in forced order from each input
387
                rd_siso_arr(in_sel) <= src_in;          -- no sop, remain at current input to wait for a frame     
388
            END CASE;
389
          END IF;
390
        WHEN OTHERS => -- s_output
391
          rd_siso_arr(in_sel) <= src_in;                -- output the rest of the selected input frame
392
          IF pend_src_out_arr(in_sel).eop='1' THEN
393
            rd_siso_arr <= (OTHERS=>c_dp_siso_hold);    -- the eop is there, stop reading this input
394
            IF src_in.ready='1' THEN
395
              nxt_in_sel            <= next_sel;        -- the pend_src_out_arr(in_sel).eop will be output, so continue to next input. 
396
              rd_siso_arr(next_sel) <= src_in;
397
              nxt_state <= s_idle;
398
            END IF;
399
          END IF;
400
      END CASE;
401
 
402
      -- Pass on frame level flow control
403
      FOR I IN 0 TO g_nof_input-1 LOOP
404
        rd_siso_arr(I).xon <= src_in.xon;
405
 
406
        IF g_mode=3 THEN
407
          -- Framed MM control select input via XON
408
          rd_siso_arr(I).xon <= '0';            -- force xon='0' for not selected inputs
409
          IF sel_ctrl_reg=I THEN
410
            rd_siso_arr(I).xon <= src_in.xon;   -- pass on frame level flow control for selected input
411
          END IF;
412
        END IF;
413
      END LOOP;
414
    END PROCESS;
415
 
416
  END GENERATE;
417
 
418
END rtl;

powered by: WebSVN 2.1.0

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