1-------------------------------------------------------------------------------
2-- Title      : 1000base-X MAC/Endpoint - TX packet header processing unit
3-- Project    : White Rabbit
4-------------------------------------------------------------------------------
5-- File       : ep_tx_header_processor.vhd
6-- Author     : Tomasz Wlostowski
7-- Company    : CERN BE-CO-HT
8-- Created    : 2009-06-22
9-- Last update: 2017-02-02
10-- Platform   : FPGA-generic
11-- Standard   : VHDL'93
12-------------------------------------------------------------------------------
13-- Description: Processes headers and OOBs of the packets to be transmitted.
14-- - provides a Wishbone-B4 interface to the host
15-- - embeds source MAC addresses if they aren't defined by the host
16-- - decodes TX OOB data and passes it to the timestamping unit
17-------------------------------------------------------------------------------
18--
19-- Copyright (c) 2009 - 2017 CERN
20--
21-- This source file is free software; you can redistribute it
22-- and/or modify it under the terms of the GNU Lesser General
23-- Public License as published by the Free Software Foundation;
24-- either version 2.1 of the License, or (at your option) any
25-- later version.
26--
27-- This source is distributed in the hope that it will be
28-- useful, but WITHOUT ANY WARRANTY; without even the implied
29-- warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
30-- PURPOSE.  See the GNU Lesser General Public License for more
31-- details.
32--
33-- You should have received a copy of the GNU Lesser General
34-- Public License along with this source; if not, download it
35-- from http://www.gnu.org/licenses/lgpl-2.1.html
36--
37-------------------------------------------------------------------------------
38
39
40library ieee;
41use ieee.std_logic_1164.all;
42use ieee.numeric_std.all;
43
44library work;
45use work.gencores_pkg.all;
46use work.genram_pkg.all;
47use work.wr_fabric_pkg.all;
48use work.endpoint_private_pkg.all;
49use work.endpoint_pkg.all;
50use work.ep_wbgen2_pkg.all;
51
52entity ep_tx_header_processor is
53  generic(
54    g_with_packet_injection : boolean;
55    g_with_timestamper      : boolean;
56    g_force_gap_length      : integer;
57    g_runt_padding          : boolean
58    );
59
60  port (
61    clk_sys_i : in std_logic;
62    rst_n_i   : in std_logic;
63
64------------------------------------------------------------------------------
65-- Physical Coding Sublayer (PCS) interface
66------------------------------------------------------------------------------
67
68    src_fab_o  : out t_ep_internal_fabric;
69    src_dreq_i : in  std_logic;
70
71    pcs_busy_i  : in std_logic;
72    pcs_error_i : in std_logic;
73
74-------------------------------------------------------------------------------
75-- WRF Sink (see WRF specification for the details)
76-------------------------------------------------------------------------------
77
78    wb_snk_i : in  t_wrf_sink_in;
79    wb_snk_o : out t_wrf_sink_out;
80
81-------------------------------------------------------------------------------
82-- Flow Control Unit signals
83-------------------------------------------------------------------------------
84
85-- TX send pause frame - when active, the framer will send a PAUSE frame
86-- as soon as possible. The pause quanta must be provided on tx_pause_delay_i input.
87    fc_pause_req_i   : in std_logic;
88    fc_pause_delay_i : in std_logic_vector(15 downto 0);
89
90-- TX send pause acknowledge - active after the current pause send request has
91-- been completed
92    fc_pause_ready_o : out std_logic;
93
94-- When active, the framer will allow for packet transmission.
95    fc_flow_enable_i : in std_logic;
96
97-------------------------------------------------------------------------------
98-- OOB/TSU signals
99-------------------------------------------------------------------------------
100
101-- Port ID value
102    txtsu_port_id_o      : out std_logic_vector(4 downto 0);
103-- Frame ID value
104    txtsu_fid_o          : out std_logic_vector(16 -1 downto 0);
105-- Encoded timestamps
106    txtsu_ts_value_o     : out std_logic_vector(28 + 4 - 1 downto 0);
107    txtsu_ts_incorrect_o : out std_logic;
108
109-- TX timestamp strobe: HI tells the TX timestamping unit that a timestamp is
110-- available on txtsu_ts_value_o, txtsu_fid_o andd txtsu_port_id_o. The correctness
111-- of the timestamping is indiacted on txtsu_ts_incorrect_o. Line remains HI
112-- until assertion of txtsu_ack_i.
113    txtsu_stb_o : out std_logic;
114
115-- TX timestamp acknowledge: HI indicates that TXTSU has successfully received
116-- the timestamp
117    txtsu_ack_i : in std_logic;
118
119---------------------------------------------------------------------------
120-- Timestamp input from the timestamping unit
121---------------------------------------------------------------------------
122    txts_timestamp_i       : in std_logic_vector(31 downto 0);
123    txts_timestamp_valid_i : in std_logic;
124
125-------------------------------------------------------------------------------
126-- Control registers
127-------------------------------------------------------------------------------
128    ep_ctrl_i           : in std_logic;
129    regs_i : in t_ep_out_registers
130
131    );
132
133
134end ep_tx_header_processor;
135
136architecture behavioral of ep_tx_header_processor is
137
138  constant c_IFG_LENGTH : integer := g_force_gap_length ;--0;
139  constant c_MIN_FRAME_THR  : integer := 30;
140  constant c_MIN_QFRAME_THR : integer := 32; -- we need to pad more 802.1q
141                                             -- tagged frame if it's going to be
142                                             -- untagged later in the tx_path
143
144  type t_tx_framer_state is (TXF_IDLE, TXF_DELAYED_SOF, TXF_ADDR, TXF_DATA, TXF_GAP, TXF_PAD, TXF_ABORT, TXF_STORE_TSTAMP);
145
146-- general signals
147  signal state   : t_tx_framer_state;
148  signal counter : unsigned(13 downto 0);
149
150-- Flow Control-related signals
151  signal tx_pause_mode  : std_logic;
152
153  signal snk_valid : std_logic;
154
155  signal sof_p1, eof_p1, abort_p1, error_p1 : std_logic;
156  signal snk_cyc_d0                         : std_logic;
157
158  signal stored_status : t_wrf_status_reg;
159
160  type t_oob_fsm_state is (OOB_IDLE, OOB_1, OOB_2);
161
162  signal oob_state : t_oob_fsm_state;
163  signal oob       : t_wrf_oob;
164
165  signal wb_out         : t_wrf_sink_out;
166  signal decoded_status : t_wrf_status_reg;
167
168  signal abort_now : std_logic;
169  signal stall_int : std_logic;
170  signal tx_en        : std_logic;
171  signal ep_ctrl     : std_logic;
172  signal bitsel_d    : std_logic;
173  signal needs_padding  : std_logic;
174  signal to_be_untagged : std_logic;
175  signal sof_reg     : std_logic;
176
177  function b2s (x : boolean)
178    return std_logic is
179  begin
180    if(x) then
181      return '1';
182    else
183      return '0';
184    end if;
185  end function;
186
187  function f_pick (cond : boolean; when_1 : std_logic_vector; when_0 : std_logic_vector)
188    return std_logic_vector is
189  begin
190    if(cond) then
191      return when_1;
192    else
193      return when_0;
194    end if;
195  end function;
196
197  function f_pick (cond : std_logic; when_1 : std_logic_vector; when_0 : std_logic_vector)
198    return std_logic_vector is
199  begin
200    if(cond = '1') then
201      return when_1;
202    else
203      return when_0;
204    end if;
205  end function;
206
207  function f_pick (cond : boolean; when_1 : std_logic ; when_0 : std_logic)
208    return std_logic is
209  begin
210    if(cond) then
211      return when_1;
212    else
213      return when_0;
214    end if;
215  end function;
216
217  function f_fabric_2_slv (
218    in_i : t_wrf_sink_in;
219    in_o : t_wrf_sink_out) return std_logic_vector is
220    variable tmp : std_logic_vector(31 downto 0);
221  begin
222    tmp(15 downto 0)  := in_i.dat;
223    tmp(17 downto 16) := in_i.adr;
224    tmp(19 downto 18) := in_i.sel;
225    tmp(20)           := in_i.cyc;
226    tmp(21)           := in_i.stb;
227    tmp(22)           := in_i.we;
228    tmp(23)           := in_o.ack;
229    tmp(24)           := in_o.stall;
230    tmp(25)           := in_o.err;
231    tmp(26)           := in_o.rty;
232    return tmp;
233  end f_fabric_2_slv;
234
235begin  -- behavioral
236
237  p_detect_frame : process(clk_sys_i)
238  begin
239    if rising_edge(clk_sys_i) then
240      if rst_n_i = '0' then
241        snk_cyc_d0 <= '0';
242      else
243        snk_cyc_d0 <= wb_snk_i.cyc;
244      end if;
245    end if;
246  end process;
247
248  sof_p1 <= not snk_cyc_d0 and wb_snk_i.cyc;
249  eof_p1 <= snk_cyc_d0 and not wb_snk_i.cyc;
250
251  snk_valid <= (wb_snk_i.cyc and wb_snk_i.stb and wb_snk_i.we) and not wb_out.stall;
252
253  decoded_status <= f_unmarshall_wrf_status(wb_snk_i.dat);
254
255  error_p1 <= snk_valid and b2s(wb_snk_i.adr = c_WRF_STATUS) and decoded_status.error;
256
257-- abort_now <= '1' when (state /= TXF_IDLE and state /= TXF_GAP) and (regs_i.ecr_tx_en_o = '0' or error_p1 = '1') else '0';
258 abort_now <= '1' when (state /= TXF_IDLE and state /= TXF_GAP) and (tx_en = '0' or error_p1 = '1') else
259              '1' when (state = TXF_ABORT and wb_snk_i.cyc = '1' ) else
260              '0'; -- ML
261
262  GEN_PADDING: if(g_runt_padding) generate
263    needs_padding <= '1' when( (to_be_untagged = '1' and counter < c_MIN_QFRAME_THR) or
264                                counter < c_MIN_FRAME_THR) else
265                     '0';
266  end generate;
267  GEN_NOPADDING: if( not g_runt_padding) generate
268    -- even if padding is disabled, we still need to pad short 802.1q frames
269    -- that will be untagged
270    needs_padding <= '1' when (to_be_untagged = '1' and counter < c_MIN_QFRAME_THR) else
271                     '0';
272  end generate;
273
274  process(clk_sys_i)
275  begin
276    if rising_edge(clk_sys_i) then
277      if(rst_n_i='0') then
278        sof_reg <= '0';
279      elsif(sof_p1='1') then
280        sof_reg <= '1';
281      elsif(state = TXF_ADDR) then
282        sof_reg <= '0';
283      end if;
284    end if;
285  end process;
286
287  p_store_status : process(clk_sys_i)
288  begin
289    if rising_edge(clk_sys_i) then
290
291      if rst_n_i = '0' or tx_pause_mode = '1' then
292        stored_status.has_smac <= '0';
293        stored_status.is_hp    <= '0';
294        stored_status.has_crc  <= '0';
295      else
296        if(snk_valid = '1' and wb_snk_i.adr = c_WRF_STATUS) then
297          stored_status <= f_unmarshall_wrf_status(wb_snk_i.dat);
298        end if;
299      end if;
300    end if;
301  end process;
302
303  -----------------------------------------------------------------------------
304  -- Out-of-band handling state machine. When a packet comes with OOB info
305  -- (frame ID), it is registered here. Then the main FSM waits until the TX
306  -- FIFO of the endpoint is completely empty and pushes the last timestamp
307  -- from the PCS to the TX Timestamping Unit
308  -----------------------------------------------------------------------------
309  gen_ts_supported : if(g_with_timestamper) generate
310    p_oob_fsm : process(clk_sys_i)
311    begin
312      if rising_edge(clk_sys_i) then
313        if (rst_n_i = '0' or state = TXF_ADDR) then
314          oob_state    <= OOB_1;
315          oob.valid    <= '0';
316          oob.oob_type <= (others => '0');
317        else
318
319          case oob_state is
320            when OOB_1 =>
321              if(snk_valid = '1' and wb_snk_i.adr = c_WRF_OOB) then
322                oob.oob_type <= wb_snk_i.dat(15 downto 12);
323                oob_state    <= OOB_2;
324                oob.valid    <= '0';
325              end if;
326
327            when OOB_2 =>
328              if(snk_valid = '1' and wb_snk_i.adr = c_WRF_OOB and oob.oob_type = c_WRF_OOB_TYPE_TX) then
329                oob.frame_id <= wb_snk_i.dat(15 downto 0);
330                oob_state    <= OOB_IDLE;
331                oob.valid    <= '1';
332              end if;
333
334            when OOB_IDLE =>
335              oob_state <= OOB_IDLE;
336          end case;
337        end if;
338      end if;
339    end process;
340  end generate gen_ts_supported;
341
342  p_tx_fsm : process (clk_sys_i)
343  begin  -- process
344    if rising_edge(clk_sys_i) then
345      if(rst_n_i = '0') then
346        state <= TXF_IDLE;
347
348        src_fab_o.has_rx_timestamp   <= '0';
349        src_fab_o.rx_timestamp_valid <= '0';
350        src_fab_o.dvalid             <= '0';
351        src_fab_o.ERROR              <= '0';
352        src_fab_o.sof                <= '0';
353        src_fab_o.eof                <= '0';
354        src_fab_o.bytesel            <= '0';
355
356        wb_out.err <= '0';
357        wb_out.rty <= '0';
358
359        tx_pause_mode <= '0';
360
361        fc_pause_ready_o <= '1';
362
363        txtsu_stb_o <= '0';
364        bitsel_d  <= '0';
365        to_be_untagged <= '0';
366
367      else
368
369        -- we are in the middle of the frame and the framer has got suddenly
370        -- disabled or we've received an ABORT command or an error occured in the PCS:
371
372        if(pcs_error_i = '1') then
373          state      <= TXF_IDLE;
374          wb_out.rty <= '1';
375          ----------------------------------------------------------------------------------
376          src_fab_o.error  <= '1'; -- nasty-bug-fix: it might happen that PCS throws error
377                                   -- to a previous frame, but we already start sending
378                                   -- the next one, in this case the frame is stopped being
379                                   -- sent but PCS does not know why... in the end we see
380                                   -- two SOFs in PACs
381          ----------------------------------------------------------------------------------
382        elsif(abort_now = '1') then
383          -- abort the current frame
384          state            <= TXF_ABORT;
385          src_fab_o.sof    <= '0';
386          src_fab_o.dvalid <= '0';
387
388        else
389
390          case state is
391
392-------------------------------------------------------------------------------
393-- TX FSM state IDLE: awaits incoming TX frames
394-------------------------------------------------------------------------------
395
396            when TXF_IDLE =>            -- idle state - wait for the next frame
397
398              wb_out.err <= '0';
399              wb_out.rty <= '0';
400
401              txtsu_stb_o <= '0';
402              bitsel_d    <= '0';
403
404              src_fab_o.error  <= '0';
405              src_fab_o.eof    <= '0';
406              src_fab_o.dvalid <= '0';
407              src_fab_o.bytesel <= '0';
408              to_be_untagged    <= '0';
409
410              -- Check start-of-frame and send-pause signals and eventually
411              -- commence frame transmission
412
413--             if(src_dreq_i = '1' and (sof_p1 = '1' or fc_pause_req_i = '1') and tx_en = '1') then --ML:removed
414--            EXPLANATION: removed src_dreq_i = '1' as the cycle can start on stall HIGH (dreq_i LOW),
415--            it means that if we wait for dreq to be high.... we can miss SOF and thus entire frame.
416--            New state added to include a case where SOF (start of cycle) starts when dreq is LOW.
417--            (we cannot just go to TXF_ADDR... it is because the PCS needs the minimal gap to add CRC)
418              if((sof_p1 = '1' or sof_reg='1' or fc_pause_req_i = '1') and tx_en = '1') then --ML
419
420                fc_pause_ready_o <= '0';
421                tx_pause_mode    <= fc_pause_req_i;
422
423                counter       <= (others => '0');
424
425                if(src_dreq_i = '1') then
426                  state         <= TXF_ADDR;
427                  src_fab_o.sof <= '1';
428                end if;
429
430              else
431                src_fab_o.sof <= '0';
432              end if;
433
434-------------------------------------------------------------------------------
435-- TX FSM (ML-added): this state takes into accunt the rare case where SOF happens
436-- when dreq is LOW (PCS not ready). So we wait for dreq HIGH and STALL in the
437-- meanttime (see process at the end)
438-------------------------------------------------------------------------------
439            when TXF_DELAYED_SOF =>
440
441              if(src_dreq_i = '1') then
442                state         <= TXF_ADDR;
443                src_fab_o.sof <= '1';
444             end if;
445-------------------------------------------------------------------------------
446-- TX FSM state HEADER: processes the frame header, send pause frames
447-- if compiled without packet injection support.
448-------------------------------------------------------------------------------
449
450            when TXF_ADDR =>
451              src_fab_o.sof <= '0';
452
453              if (src_dreq_i = '1' and ((snk_valid = '1' and wb_snk_i.adr = c_WRF_DATA) or (tx_pause_mode = '1' and not g_with_packet_injection))) then
454
455                counter          <= counter + 1;
456                src_fab_o.dvalid <= '1';
457
458                case counter(3 downto 0) is
459                  when x"0" =>
460                    src_fab_o.data <= f_pick(tx_pause_mode = '1' and not g_with_packet_injection, x"0180", wb_snk_i.dat);
461                  when x"1" =>
462                    src_fab_o.data <= f_pick(tx_pause_mode = '1' and not g_with_packet_injection, x"c200", wb_snk_i.dat);
463                  when x"2" =>
464                    src_fab_o.data <= f_pick(tx_pause_mode = '1' and not g_with_packet_injection, x"0001", wb_snk_i.dat);
465                  when x"3" =>
466                    src_fab_o.data <= f_pick(stored_status.has_smac, wb_snk_i.dat, regs_i.mach_o);
467                  when x"4" =>
468                    src_fab_o.data <= f_pick(stored_status.has_smac, wb_snk_i.dat, regs_i.macl_o(31 downto 16));
469                  when x"5" =>
470                    src_fab_o.data <= f_pick(stored_status.has_smac, wb_snk_i.dat, regs_i.macl_o(15 downto 0));
471                    if(tx_pause_mode = '0' or g_with_packet_injection) then
472                      state <= TXF_DATA;
473                    end if;
474                  when x"6" =>
475                    src_fab_o.data <= f_pick(g_with_packet_injection, "XXXXXXXXXXXXXXXX", x"8808");
476                    to_be_untagged <= f_pick(wb_snk_i.dat = x"8100" and
477                                             regs_i.vcr0_qmode_o = c_QMODE_PORT_ACCESS, '1', '0');
478                  when x"7" =>
479                    src_fab_o.data <= f_pick(g_with_packet_injection, "XXXXXXXXXXXXXXXX", x"0001"); -- peterj: IEEE 802.3 Table 31A-1 MAC control codes PAUSE (Annex 31B)
480                  when x"8" =>
481                    src_fab_o.data <= f_pick(g_with_packet_injection, "XXXXXXXXXXXXXXXX", fc_pause_delay_i); -- ML: bug ??? (forget optcode: 0x0001)
482                    state          <= TXF_PAD;
483                  when others =>
484                    state <= TXF_PAD;
485                end case;
486
487                src_fab_o.addr   <= c_WRF_DATA;
488
489              else
490                src_fab_o.dvalid <= '0';
491                src_fab_o.data   <= (others => 'X');
492                src_fab_o.addr   <= (others => 'X');
493              end if;
494
495-------------------------------------------------------------------------------
496-- TX FSM state PAD: pads a pause frame to 64 bytes.
497-------------------------------------------------------------------------------
498
499            when TXF_PAD =>
500
501              if(src_dreq_i = '1') then
502                counter <= counter + 1;
503
504                src_fab_o.data   <= (others => '0');
505                src_fab_o.dvalid <= '1';
506                src_fab_o.addr   <= (others => '0');
507
508                if( (to_be_untagged = '1' and counter = c_MIN_QFRAME_THR-1) or
509                    (to_be_untagged = '0' and counter = c_MIN_FRAME_THR-1) ) then
510                  state <= TXF_GAP;
511                  src_fab_o.eof    <= '1';
512                end if;
513
514              else
515                src_fab_o.data   <= (others => '0');
516                src_fab_o.dvalid <= '0';
517                src_fab_o.addr   <= (others => '0');
518              end if;
519
520-------------------------------------------------------------------------------
521-- TX FSM state DATA: trasmits frame payload
522-------------------------------------------------------------------------------
523
524            when TXF_DATA =>
525
526              -- ML: added this EOF force LOW to make sure that EOF is single cycle, withouth
527              -- this, it might have happened that we had eof_p1 but PCS was busy, so we set
528              -- src_fab_o.eof to HIGH but actually did not exit the TXF_DATA state... this
529              -- caused EOF to be longer than one cycle
530              src_fab_o.eof   <= '0';
531
532              if (counter = x"6") then
533                to_be_untagged <= f_pick(wb_snk_i.dat = x"8100" and
534                                         regs_i.vcr0_qmode_o = c_QMODE_PORT_ACCESS, '1', '0');
535              end if;
536
537              if((wb_snk_i.adr = c_WRF_OOB or eof_p1='1') and needs_padding='1') then
538                state <= TXF_PAD;
539              elsif(eof_p1 = '1' and needs_padding='0') then
540                src_fab_o.eof <= '1';
541                counter       <= (others => '0');
542
543                if(g_force_gap_length = 0 and bitsel_d = '1') then -- only for odd
544
545                  -- Submit the TX timestamp to the TXTSU queue
546                  if(oob.valid = '1' and oob.oob_type = c_WRF_OOB_TYPE_TX) then
547                    if(pcs_busy_i = '0') then
548                      txtsu_stb_o          <= '1';
549                      txtsu_ts_incorrect_o <= not txts_timestamp_valid_i;
550                      txtsu_ts_value_o     <= txts_timestamp_i;
551                      txtsu_port_id_o      <= regs_i.ecr_portid_o;
552                      txtsu_fid_o          <= oob.frame_id;
553                      state                <= TXF_STORE_TSTAMP;
554                    else
555                       -- wait in the GAP state for pcs_busy_i LOW
556                      state                <= TXF_GAP;
557                    end if;                                      ---if(pcs_busy_i = '0') then
558                  else
559                    -- dont need timestamp, don't need GAP, just go to IDLE
560                    state <= TXF_IDLE;
561                  end if;                                        -- if(oob.valid = '1' and oob.oob_type = c_WRF_OOB_TYPE_TX) then
562                else -- need some GAP
563                  state         <= TXF_GAP;
564                end if;                                          -- f(g_force_gap_length = 0 and bitsel_d = '1') then
565              end if;                                            -- if(eof_p1 = '1') then
566
567              if(snk_valid = '1' and wb_snk_i.adr = c_WRF_DATA) then
568                src_fab_o.data    <= wb_snk_i.dat;
569                src_fab_o.dvalid  <= '1';
570                src_fab_o.bytesel <= (not wb_snk_i.sel(0)) and (not needs_padding);
571                counter <= counter + 1;
572              else
573                src_fab_o.dvalid  <= '0';
574                src_fab_o.data    <= (others => 'X');
575                src_fab_o.bytesel <= '0';
576              end if;
577
578              if(wb_snk_i.sel(0) = '0') then
579                bitsel_d <='1';
580              end if;
581
582              if(needs_padding='1') then
583                src_fab_o.addr  <= (others=>'0');
584              else
585                src_fab_o.addr    <= wb_snk_i.adr;
586              end if;
587
588-------------------------------------------------------------------------------
589-- TX FSM states: WAIT_CRC, EMBED_CRC: dealing with frame checksum field
590-------------------------------------------------------------------------------
591
592            when TXF_GAP =>
593              src_fab_o.eof    <= '0';
594              src_fab_o.error  <= '0';
595              src_fab_o.dvalid <= '0';
596              wb_out.err       <= '0';
597              wb_out.rty       <= '0';
598              src_fab_o.bytesel <= '0';
599
600              if(counter >= c_IFG_LENGTH or g_force_gap_length = 0) then
601
602                -- Submit the TX timestamp to the TXTSU queue
603                if(oob.valid = '1' and oob.oob_type = c_WRF_OOB_TYPE_TX) then
604                  if(pcs_busy_i = '0') then
605                    txtsu_stb_o          <= '1';
606                    txtsu_ts_incorrect_o <= not txts_timestamp_valid_i;
607                    txtsu_ts_value_o     <= txts_timestamp_i;
608                    txtsu_port_id_o      <= regs_i.ecr_portid_o;
609                    txtsu_fid_o          <= oob.frame_id;
610                    state                <= TXF_STORE_TSTAMP;
611                  end if;
612                else
613                  state <= TXF_IDLE;
614                end if;
615
616              else
617                counter <= counter + 1;
618              end if;
619
620            when TXF_STORE_TSTAMP =>  -- to slow ??? anyway, we can finish the frame
621
622              src_fab_o.eof    <= '0';
623              src_fab_o.error  <= '0';
624              src_fab_o.dvalid <= '0';
625              wb_out.err       <= '0';
626              wb_out.rty       <= '0';
627              src_fab_o.bytesel<= '0';
628
629              if(txtsu_ack_i = '1') then
630                txtsu_stb_o <= '0';
631                state       <= TXF_IDLE;
632              end if;
633
634-------------------------------------------------------------------------------
635-- TX FSM state ABORT: signalize underlying PCS block to abort the frame
636-- immediately, corrupting its contents
637-------------------------------------------------------------------------------
638            when TXF_ABORT =>
639              src_fab_o.sof    <= '0';
640              src_fab_o.dvalid <= '1';
641              src_fab_o.error  <= '1';
642
643              counter <= (others => '0');
644              state   <= TXF_IDLE;
645
646          end case;
647        end if;
648      end if;
649    end if;
650  end process;
651
652  tx_en <= regs_i.ecr_tx_en_o and ep_ctrl and ep_ctrl_i;
653
654  --p_gen_stall : process(src_dreq_i, state, regs_i, wb_snk_i, snk_cyc_d0, tx_en)
655  p_gen_stall : process(src_dreq_i, state, tx_en, wb_snk_i, eof_p1)
656  begin
657    --if(regs_i.ecr_tx_en_o = '0') then
658    if(tx_en = '0') then --ML
659      wb_out.stall <= '0';              -- /dev/null if TX disabled
660--     elsif((wb_snk_i.cyc xor snk_cyc_d0) = '1') then
661--    elsif(wb_snk_i.cyc = '1' and snk_cyc_d0 = '0') then -- ML: do it only at the SOF, not EOF
662--      wb_out.stall <= '1';              -- /block for 1 cycle right upon
663                                        -- detection of a packet, so the FSM
664                                        -- has time to catch up
665
666    -- stall at EOF - the SWcore should not send anything, but just in case, not to miss
667    -- SOF... the next cycle will be TXF_GAP (also stalling) or TXF_IDLE (can accept new frames)
668    elsif(eof_p1 = '1') then -- accept OOB as is
669      wb_out.stall <= '1';
670
671    -- when data is flowing (TXF_DATA) or we expect data (TXF_IDLE) stall only when no dreq_i
672    -- from other modules
673---------------------------------------------------------------------------------------------
674-- ML: when error at the very end of the frame (e.g. due to jambo frame), stall happenend
675-- at the last cycle before cyc DOWN, subsequently, cycle did not finish and switch hanged
676---------------------------------------------------------------------------------------------
677--     elsif(src_dreq_i = '1' and state /= TXF_GAP and state /= TXF_ABORT and state /= TXF_DELAYED_SOF and state /= TXF_STORE_TSTAMP) then
678---------------------------------------------------------------------------------------------
679    elsif(src_dreq_i = '1' and state /= TXF_PAD and state /= TXF_GAP  and state /= TXF_DELAYED_SOF and state /= TXF_STORE_TSTAMP) then
680      wb_out.stall <= '0';              -- during data/header phase - whenever
681                                        -- the sink is ready to accept data
682
683    -- when we receive OOB, there we have always resources/possibilties to accept it
684    -- since it is dumped in here, so we prevent dreq_i going LOW from stopping
685    -- to receive OOB
686    elsif(wb_snk_i.adr = c_WRF_OOB and wb_snk_i.cyc = '1') then -- accept OOB as is
687      wb_out.stall <= '0';
688
689    -- one other option renderds stall
690    else
691      wb_out.stall <= '1';
692    end if;
693  end process;
694
695  p_gen_ack : process(clk_sys_i)
696  begin
697    if rising_edge(clk_sys_i) then
698      wb_out.ack <= snk_valid;
699    end if;
700  end process;
701
702  -- in theory, this should not happen: we don't send frames to ports which are DOWN, but..
703  -- we make sure that we don't start sending frames on the PHY in the middle of the frame...
704  -- the TX is enabled only when we don't receive any frames from SWcore
705  p_ctrl: process(clk_sys_i)
706  begin
707    if rising_edge(clk_sys_i) then
708      if(rst_n_i = '0') then
709        ep_ctrl  <= '1';
710      else
711        if(ep_ctrl_i = '0') then
712          ep_ctrl <= '0';
713        elsif(ep_ctrl_i = '1' and wb_snk_i.cyc = '0') then
714          ep_ctrl <= '1';
715        end if; --ep_ctr
716      end if;-- rst
717    end if;  -- clk
718  end process;
719
720  wb_snk_o <= wb_out;
721
722end behavioral;
723
724