diff --git a/modules/wr_endpoint/endpoint_private_pkg.vhd b/modules/wr_endpoint/endpoint_private_pkg.vhd
index 10f4415be0dfc43c3724e58de09600d00ceb2828..b695611b9dfea2d3e08f8e51bb68759fec9054e6 100644
--- a/modules/wr_endpoint/endpoint_private_pkg.vhd
+++ b/modules/wr_endpoint/endpoint_private_pkg.vhd
@@ -283,6 +283,23 @@ package endpoint_private_pkg is
       regs_b             : inout t_ep_registers);
   end component;
 
+  component ep_rx_bypass_queue
+    generic (
+      g_size  : integer;
+      g_width : integer);
+    port (
+      rst_n_i : in  std_logic;
+      clk_i   : in  std_logic;
+      d_i     : in  std_logic_vector(g_width-1 downto 0);
+      valid_i : in  std_logic;
+      dreq_o  : out std_logic;
+      q_o     : out std_logic_vector(g_width-1 downto 0);
+      valid_o : out std_logic;
+      dreq_i  : in  std_logic;
+      flush_i : in  std_logic;
+      purge_i : in  std_logic);
+  end component;
+
   function f_pack_fifo_contents (
     data      : std_logic_vector;
     sof       : std_logic;
diff --git a/modules/wr_endpoint/ep_clock_alignment_fifo.vhd b/modules/wr_endpoint/ep_clock_alignment_fifo.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..cc23166bd51ad7891e71c128ac09a6e0d3fb1488
--- /dev/null
+++ b/modules/wr_endpoint/ep_clock_alignment_fifo.vhd
@@ -0,0 +1,100 @@
+library ieee;
+use ieee.std_logic_1164.all;
+
+use work.genram_pkg.all;
+use work.endpoint_private_pkg.all;
+
+entity ep_clock_alignment_fifo is
+
+  generic(
+    g_size                  : integer := 64;
+    g_almostfull_threshold : integer := 56;
+    g_early_eof             : boolean := false
+    );
+
+  port(
+    rst_n_i : in std_logic;
+
+    clk_wr_i : in std_logic;
+    clk_rd_i : in std_logic;
+
+    we_i : in std_logic;
+    dreq_i: in std_logic;
+
+    fab_i : in  t_ep_internal_fabric;
+    fab_o : out t_ep_internal_fabric;
+
+    full_o       : out std_logic;
+    empty_o      : out std_logic;
+    almostfull_o : out std_logic
+    );
+end ep_clock_alignment_fifo;
+
+architecture structural of ep_clock_alignment_fifo is
+  signal fifo_in   : std_logic_vector(17 downto 0);
+  signal fifo_out  : std_logic_vector(17 downto 0);
+  signal rx_rdreq  : std_logic;
+  signal empty_int : std_logic;
+  signal valid_int : std_logic;
+  
+begin
+
+  fifo_in <= f_pack_fifo_contents (
+    fab_i.data,
+    fab_i.sof,
+    fab_i.eof,
+    fab_i.bytesel,
+    fab_i.error,
+    g_early_eof);
+
+-- Clock adjustment FIFO
+  U_FIFO : generic_async_fifo
+    generic map (
+      g_data_width            => 18,
+      g_size                  => g_size,
+      g_with_wr_almost_full   => true,
+      g_almost_full_threshold => g_almostfull_threshold)
+
+    port map (
+      rst_n_i           => rst_n_i,
+      clk_wr_i          => clk_wr_i,
+      d_i               => fifo_in,
+      we_i              => we_i,
+      wr_empty_o        => open,
+      wr_full_o         => full_o,
+      wr_almost_empty_o => open,
+      wr_almost_full_o  => almostfull_o,
+      wr_count_o        => open,
+      clk_rd_i          => clk_rd_i,
+      q_o               => fifo_out,
+      rd_i              => rx_rdreq,
+      rd_empty_o        => empty_int,
+      rd_full_o         => open,
+      rd_almost_empty_o => open,
+      rd_almost_full_o  => open,
+      rd_count_o        => open);
+
+  rx_rdreq <= (not empty_int) and dreq_i;
+
+  p_gen_valid : process (clk_rd_i, rst_n_i)
+  begin
+    if rising_edge(clk_rd_i) then
+      if(rst_n_i = '0') then
+        valid_int <= '0';
+      else
+        valid_int <= rx_rdreq;
+      end if;
+    end if;
+  end process;
+
+  -- FIFO output data formatting
+  fab_o.sof     <= f_fifo_is_sof(fifo_out, valid_int);
+  fab_o.eof     <= f_fifo_is_eof(fifo_out, valid_int);
+  fab_o.error   <= f_fifo_is_error(fifo_out, valid_int);
+  fab_o.dvalid  <= f_fifo_is_data(fifo_out, valid_int);
+  fab_o.bytesel <= f_fifo_is_single_byte(fifo_out, valid_int);
+  fab_o.data    <= fifo_out(15 downto 0);
+
+  empty_o <= empty_int;
+  
+end structural;
diff --git a/modules/wr_endpoint/ep_packet_filter.vhd b/modules/wr_endpoint/ep_packet_filter.vhd
index 9171bde507c5e739f06094dfde20f2659fd389b5..9c74724d54b8e1670998eecfba3cab71d922d35e 100644
--- a/modules/wr_endpoint/ep_packet_filter.vhd
+++ b/modules/wr_endpoint/ep_packet_filter.vhd
@@ -117,6 +117,7 @@ architecture behavioral of ep_packet_filter is
   signal pmem_addr  : unsigned(c_PC_SIZE-1 downto 0);
   signal pmem_rdata : std_logic_vector(15 downto 0);
 
+  signal mm_addr  : std_logic_vector(c_PC_SIZE-1 downto 0);
   signal mm_write           : std_logic;
   signal mm_rdata, mm_wdata : std_logic_vector(35 downto 0);
 
@@ -127,7 +128,7 @@ architecture behavioral of ep_packet_filter is
 begin  -- behavioral
   regs_b  <= c_ep_registers_init_value;
 
-  mm_write <= not regs_b.ecr_rx_en_o and regs_b.pfcr0_mm_write_o and regs_b.pfcr0_mm_write_wr_o;
+  mm_write <= not regs_b.pfcr0_enable_o and regs_b.pfcr0_mm_write_o and regs_b.pfcr0_mm_write_wr_o;
   mm_wdata <= regs_b.pfcr0_mm_data_msb_o & regs_b.pfcr1_mm_data_lsb_o;
 
   U_microcode_ram : generic_spram
@@ -139,10 +140,12 @@ begin  -- behavioral
       clk_i   => clk_sys_i,
       bwe_i   => "11111",
       we_i    => mm_write,
-      a_i     => regs_b.pfcr0_mm_addr_o,
+      a_i     => mm_addr,
       d_i     => mm_wdata,
       q_o     => mm_rdata);
 
+  mm_addr <= regs_b.pfcr0_mm_addr_o when mm_write = '1' else std_logic_vector(pc);
+  
 
   U_backlog_ram : generic_dpram
     generic map (
@@ -225,7 +228,7 @@ begin  -- behavioral
     end if;
   end process;
 
-  result_cmp <= '1' when ((pmem_rdata and mask) xor mask) = x"0000" else '0';
+  result_cmp <= '1' when ((pmem_rdata and mask) xor insn.cmp_value) = x"0000" else '0';
 
   insn <= f_decode_insn(ir);
   ra   <= f_pick_reg(regs, insn.ra) when insn.mode = c_MODE_LOGIC else result_cmp;
@@ -235,7 +238,7 @@ begin  -- behavioral
   result1 <= f_eval(ra, rb, insn.op);
   result2 <= f_eval(result1, rc, insn.op2);
 
-  rd <= result1 when insn.mode = c_MODE_LOGIC else result2;
+  rd <= result2 when insn.mode = c_MODE_LOGIC else result1;
 
   p_execute : process(clk_sys_i)
   begin
@@ -257,7 +260,11 @@ begin  -- behavioral
         done_int <= '0';
         drop_o   <= '0';
       else
-        if(stage2 = '1' and insn.fin = '1') then
+        if(regs_b.pfcr0_enable_o = '0') then
+          done_int <= '1';
+          drop_o <= '0';
+          pclass_o <= (others => '0');
+        elsif(stage2 = '1' and insn.fin = '1') then
           done_int   <= '1';
           pclass_o <= regs(31 downto 24);
           drop_o   <= regs(23);
diff --git a/modules/wr_endpoint/ep_pcs_tbi_mdio_wb.vhd b/modules/wr_endpoint/ep_pcs_tbi_mdio_wb.vhd
index c71f7e6341ca5c687e395920f3b23f9ebc3a78fe..e076adab299d9a00ff4debaec3a68024c38b51bd 100644
--- a/modules/wr_endpoint/ep_pcs_tbi_mdio_wb.vhd
+++ b/modules/wr_endpoint/ep_pcs_tbi_mdio_wb.vhd
@@ -3,7 +3,7 @@
 ---------------------------------------------------------------------------------------
 -- File           : ep_pcs_tbi_mdio_wb.vhd
 -- Author         : auto-generated by wbgen2 from pcs_regs.wb
--- Created        : Mon Aug 22 16:14:10 2011
+-- Created        : Mon Aug 22 23:38:16 2011
 -- Standard       : VHDL'87
 ---------------------------------------------------------------------------------------
 -- THIS FILE WAS GENERATED BY wbgen2 FROM SOURCE FILE pcs_regs.wb
diff --git a/modules/wr_endpoint/ep_registers_pkg.vhd b/modules/wr_endpoint/ep_registers_pkg.vhd
index 88c82cc7595296e1f70df02a41fdc32da5e3825b..7dfcfed66c64f1f91360d1b0897a35674203c4da 100644
--- a/modules/wr_endpoint/ep_registers_pkg.vhd
+++ b/modules/wr_endpoint/ep_registers_pkg.vhd
@@ -3,7 +3,7 @@
 ---------------------------------------------------------------------------------------
 -- File           : ep_registers_pkg.vhd
 -- Author         : auto-generated by wbgen2 from ep_wishbone_controller.wb
--- Created        : Mon Aug 22 16:14:10 2011
+-- Created        : Mon Aug 22 23:38:16 2011
 -- Standard       : VHDL'87
 ---------------------------------------------------------------------------------------
 -- THIS FILE WAS GENERATED BY wbgen2 FROM SOURCE FILE ep_wishbone_controller.wb
@@ -33,6 +33,7 @@ package ep_wbgen2_pkg is
     rfcr_a_giant_o                           : std_logic;
     rfcr_a_hp_o                              : std_logic;
     rfcr_keep_crc_o                          : std_logic;
+    rfcr_hpap_o                              : std_logic_vector(7 downto 0);
     rfcr_mru_o                               : std_logic_vector(13 downto 0);
     vcr0_qmode_o                             : std_logic_vector(1 downto 0);
     vcr0_fix_prio_o                          : std_logic;
@@ -93,6 +94,7 @@ package ep_wbgen2_pkg is
     rfcr_a_giant_o => 'Z',
     rfcr_a_hp_o => 'Z',
     rfcr_keep_crc_o => 'Z',
+    rfcr_hpap_o => (others => 'Z'),
     rfcr_mru_o => (others => 'Z'),
     vcr0_qmode_o => (others => 'Z'),
     vcr0_fix_prio_o => 'Z',
diff --git a/modules/wr_endpoint/ep_rx_bypass_queue.vhd b/modules/wr_endpoint/ep_rx_bypass_queue.vhd
index 56649cbedeeeaca50aa46a2ce20ba5cd236ade8f..785d13fb53ea033db94a71e24da583c9cc6a522d 100644
--- a/modules/wr_endpoint/ep_rx_bypass_queue.vhd
+++ b/modules/wr_endpoint/ep_rx_bypass_queue.vhd
@@ -1,6 +1,9 @@
 library ieee;
 use ieee.std_logic_1164.all;
 
+library unisim;
+use unisim.vcomponents.all;
+  
 entity ep_rx_bypass_queue is
   generic(
     g_size  : integer := 3;
@@ -26,47 +29,68 @@ end ep_rx_bypass_queue;
 
 architecture behavioral of ep_rx_bypass_queue is
 
-  type t_queue_entry is record
-    d     : std_logic_vector(g_width-1 downto 0);
-    valid : std_logic;
-  end record;
-
-  type t_queue_array is array(0 to g_size-1) of t_queue_entry;
-
-  function f_queue_occupation(q : t_queue_array; check_empty : std_logic) return std_logic is
+  component ep_shift_reg
+    generic (
+      g_size : integer);
+    port (
+      clk_i : in  std_logic;
+      ce_i  : in  std_logic;
+      d_i   : in  std_logic;
+      q_o   : out std_logic);
+  end component;
+  
+  function f_queue_occupation(q : std_logic_vector; check_empty : std_logic) return std_logic is
     variable i : integer;
   begin
     for i in 0 to q'length-1 loop
-      if(q(i).valid = check_empty) then
+      if(q(i) = check_empty) then
         return '0';
       end if;
     end loop;  -- i
     return '1';
   end function;
 
-  signal queue         : t_queue_array;
+  type t_queue_array is array(0 to g_width-1) of std_logic_vector(g_size-1 downto 0);
+
+  signal q_data  : t_queue_array;
+  signal q_valid : std_logic_vector(g_size-1 downto 0);
+
+
   signal qempty, qfull : std_logic;
   signal flushing      : std_logic;
   signal valid_mask    : std_logic;
-  signal valid_int : std_logic;
-  
+  signal valid_int     : std_logic;
+
+  signal sreg_enable : std_logic;
   
 begin  -- behavioral
 
-  qempty <= f_queue_occupation(queue, '1');
-  qfull  <= f_queue_occupation(queue, '0');
+  qempty <= f_queue_occupation(q_valid, '1');
+  qfull  <= f_queue_occupation(q_valid, '0');
+
+  gen_sreg : for i in 0 to g_width-1 generate
+
+    U_sreg: ep_shift_reg
+      generic map (
+        g_size => g_size)
+      port map (
+        clk_i => clk_i,
+        ce_i  => sreg_enable,
+        d_i   => d_i(i),
+        q_o   => q_o(i));
+    
+  end generate gen_sreg;
+
+
+  sreg_enable <= '1' when ((valid_i = '1') or (qempty = '0' and (flushing = '1') and valid_int = '1')) else '0';
 
   p_queue : process(clk_i)
   begin
     if rising_edge(clk_i) then
       if rst_n_i = '0' or purge_i = '1' then
-        flushing <= '0';
+        flushing   <= '0';
         valid_mask <= '0';
-        for i in 0 to queue'length-1 loop
-          queue(i).valid <= '0';
-          queue(i).d     <= (others => '0');
-        end loop;  -- i
-        
+        q_valid    <= (others => '0');
       else
         if(flushing = '1' and qempty = '1') then
           flushing <= '0';
@@ -75,21 +99,63 @@ begin  -- behavioral
         end if;
 
         valid_mask <= dreq_i;
-        
-        if ((valid_i = '1') or (qempty = '0' and (flushing = '1' or flush_i = '1') and valid_int = '1')) then
-          for i in 0 to queue'length-2 loop
-            queue(i+1) <= queue(i);--
-          end loop;  -- i
-          queue(0).d     <= d_i;
-          queue(0).valid <= valid_i;
+
+        if sreg_enable = '1' then
+          q_valid(0)                         <= valid_i;
+          q_valid(q_valid'length-1 downto 1) <= q_valid(q_valid'length-2 downto 0);
         end if;
       end if;
     end if;
   end process;
 
-  q_o     <= queue(queue'length-1).d;
-  dreq_o  <= dreq_i and not flushing;
+  dreq_o    <= dreq_i and not flushing;
   valid_int <= (qfull and valid_i) or (not qempty and flushing and valid_mask);
-  valid_o <= valid_int;
+  valid_o   <= valid_int;
   
 end behavioral;
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+
+entity ep_shift_reg is
+  generic(g_size : integer := 16);
+  port(
+    clk_i : in  std_logic;
+    ce_i  : in  std_logic;
+    d_i   : in  std_logic;
+    q_o   : out std_logic);
+end ep_shift_reg;
+
+architecture rtl of ep_shift_reg is
+  signal sreg : std_logic_vector(g_size-1 downto 0);
+  signal size : std_logic_vector(3 downto 0);
+
+  component SRL16E
+    generic (
+      INIT : bit_vector :=x"0000");
+    port (
+      Q   : out STD_ULOGIC;
+      A0  : in  STD_ULOGIC;
+      A1  : in  STD_ULOGIC;
+      A2  : in  STD_ULOGIC;
+      A3  : in  STD_ULOGIC;
+      CE  : in  STD_ULOGIC;
+      CLK : in  STD_ULOGIC;
+      D   : in  STD_ULOGIC);
+  end component;
+  
+begin  -- rtl
+  size <= std_logic_vector(to_unsigned(g_size-1, 4));
+
+  cmp_sreg: SRL16E
+    port map (
+      D   => d_i,
+      Q   => q_o,
+      CE  => ce_i,
+      CLK => clk_i,
+      A0  => size(0),
+      A1  => size(1),
+      A2  => size(2),
+      A3  => size(3));
+  end rtl;
diff --git a/modules/wr_endpoint/ep_rx_crc_size_check.vhd b/modules/wr_endpoint/ep_rx_crc_size_check.vhd
index 91976a035db9dcad364b4329c1050c3e978bb6df..dd0a6289cd4c690c86d07ffd2f49773a59f99edb 100644
--- a/modules/wr_endpoint/ep_rx_crc_size_check.vhd
+++ b/modules/wr_endpoint/ep_rx_crc_size_check.vhd
@@ -166,6 +166,8 @@ begin  -- behavioral
         rmon_o.rx_runt    <= '0';
         rmon_o.rx_crc_err <= '0';
 
+        src_fab_o.sof <= '0';
+
       else
         case state is
           when ST_WAIT_FRAME =>
@@ -178,13 +180,17 @@ begin  -- behavioral
             q_bytesel <='0';
             src_fab_o.eof     <= '0';
             src_fab_o.error   <= '0';
+            src_fab_o.sof <= '0';
 
             if(snk_fab_i.sof = '1') then
               state <= ST_DATA;
+              src_fab_o.sof <= '1';
             end if;
 
           when ST_DATA =>
 
+            src_fab_o.sof<='0';
+            
             if(snk_fab_i.dvalid= '1') then
               q_bytesel<=snk_fab_i.bytesel;
             end if;
@@ -226,7 +232,7 @@ begin  -- behavioral
     end if;
   end process;
 
-  src_fab_o.sof <= regs_b.ecr_rx_en_o and snk_fab_i.sof;
+--  src_fab_o.sof <= regs_b.ecr_rx_en_o and snk_fab_i.sof;
   src_fab_o.dvalid<=q_valid;
   src_fab_o.data <=q_data;
   src_fab_o.bytesel<=snk_fab_i.bytesel or q_bytesel;
diff --git a/modules/wr_endpoint/ep_rx_deframer.vhd b/modules/wr_endpoint/ep_rx_deframer.vhd
index 3564483bcd2c98300e4e624d6b7995278666167d..d246679ffdcf9561104561b55bbdea67b9f43b11 100644
--- a/modules/wr_endpoint/ep_rx_deframer.vhd
+++ b/modules/wr_endpoint/ep_rx_deframer.vhd
@@ -6,7 +6,7 @@
 -- Author     : Tomasz Wlostowski
 -- Company    : CERN BE-CO-HT
 -- Created    : 2009-06-22
--- Last update: 2011-08-20
+-- Last update: 2011-08-23
 -- Platform   : FPGA-generic
 -- Standard   : VHDL'93
 -------------------------------------------------------------------------------
@@ -35,17 +35,17 @@ use work.wr_fabric_pkg.all;
 
 entity ep_rx_deframer is
   generic (
-    g_with_vlans          : boolean;
-    g_with_dpi_classifier : boolean;
-    g_with_rtu            : boolean);
+    g_with_vlans          : boolean:=true;  
+    g_with_dpi_classifier : boolean:=true;
+    g_with_rtu            : boolean:=true);
   port (
     clk_sys_i : in std_logic;
     rst_n_i   : in std_logic;
 
 -- physical coding sublayer (PCS) interface
-    pcs_fab_i :in t_ep_internal_fabric;
-    pcs_dreq_o  : out std_logic;
-    pcs_busy_i  : in  std_logic;
+    pcs_fab_i  : in  t_ep_internal_fabric;
+    pcs_dreq_o : out std_logic;
+    pcs_busy_i : in  std_logic;
 
 -- OOB frame tag value and strobing signal
     oob_data_i  : in  std_logic_vector(47 downto 0);
@@ -112,7 +112,52 @@ architecture behavioral of ep_rx_deframer is
       rmon_o     : inout t_rmon_triggers;
       regs_b     : inout t_ep_registers);
   end component;
+
+  component ep_packet_filter
+    port (
+      clk_sys_i  : in    std_logic;
+      rst_n_i    : in    std_logic;
+      snk_fab_i  : in    t_ep_internal_fabric;
+      snk_dreq_o : out   std_logic;
+      src_fab_o  : out   t_ep_internal_fabric;
+      src_dreq_i : in    std_logic;
+      done_o     : out   std_logic;
+      pclass_o   : out   std_logic_vector(7 downto 0);
+      drop_o     : out   std_logic;
+      regs_b     : inout t_ep_registers);
+  end component;
   
+  component ep_rx_early_address_match
+    port (
+      clk_sys_i            : in    std_logic;
+      rst_n_i              : in    std_logic;
+      snk_fab_i            : in    t_ep_internal_fabric;
+      snk_dreq_o           : out   std_logic;
+      src_fab_o            : out   t_ep_internal_fabric;
+      src_dreq_i           : in    std_logic;
+      match_done_o         : out   std_logic;
+      match_is_hp_o        : out   std_logic;
+      match_is_pause_o     : out   std_logic;
+      match_pause_quanta_o : out   std_logic_vector(15 downto 0);
+      regs_b               : inout t_ep_registers);
+  end component;
+
+  component ep_rx_vlan_unit
+    port (
+      clk_sys_i      : in    std_logic;
+      rst_n_i        : in    std_logic;
+      snk_fab_i      : in    t_ep_internal_fabric;
+      snk_dreq_o     : out   std_logic;
+      src_fab_o      : out   t_ep_internal_fabric;
+      src_dreq_i     : in    std_logic;
+      tclass_o       : out   std_logic_vector(2 downto 0);
+      tclass_valid_o : out   std_logic;
+      rmon_o         : inout t_rmon_triggers;
+      regs_b         : inout t_ep_registers);
+  end component;
+
+
+
   type t_rx_deframer_state is (RXF_IDLE, RXF_DATA, RXF_FLUSH_STALL, RXF_FINISH_CYCLE, RXF_THROW_ERROR);
 
   signal state : t_rx_deframer_state;
@@ -127,37 +172,97 @@ architecture behavioral of ep_rx_deframer is
   signal is_pause     : std_logic;
 
   signal data_firstword : std_logic;
-  signal snk_dreq_int   : std_logic;
-  signal snk_dreq   : std_logic;
 
- 
+
   signal flush_stall : std_logic;
-  signal stb_int : std_logic;
-  signal fab_int : t_ep_internal_fabric;
-  
+  signal stb_int     : std_logic;
+
+  signal fab_int  : t_ep_internal_fabric;
+  signal dreq_int : std_logic;
+
   signal ack_count   : unsigned(7 downto 0);
   signal src_out_int : t_wrf_source_out;
 
   signal tmp_sel : std_logic;
   signal tmp_dat : std_logic_vector(15 downto 0);
+
+
+  type t_fab_pipe is array(integer range <>) of t_ep_internal_fabric;
+
+  signal fab_pipe  : t_fab_pipe(0 to 4);
+  signal dreq_pipe : std_logic_vector(4 downto 0);
+
+  signal ematch_done         : std_logic;
+  signal ematch_is_hp        : std_logic;
+  signal ematch_is_pause     : std_logic;
+  signal ematch_pause_quanta : std_logic_vector(15 downto 0);
+
+  signal pfilter_pclass : std_logic_vector(7 downto 0);
+  signal pfilter_drop   : std_logic;
+  signal pfilter_done   : std_logic;
   
-  
+
 begin  -- behavioral
   regs_b <= c_ep_registers_init_value;
 
+  fab_pipe(0) <= pcs_fab_i;
+  pcs_dreq_o  <= dreq_pipe(0);
+
+  U_early_addr_match : ep_rx_early_address_match
+    port map (
+      clk_sys_i            => clk_sys_i,
+      rst_n_i              => rst_n_i,
+      snk_fab_i            => fab_pipe(0),
+      snk_dreq_o           => dreq_pipe(0),
+      src_fab_o            => fab_pipe(1),
+      src_dreq_i           => dreq_pipe(1),
+      match_done_o         => ematch_done,
+      match_is_hp_o        => ematch_is_hp,
+      match_is_pause_o     => ematch_is_pause,
+      match_pause_quanta_o => ematch_pause_quanta,
+      regs_b               => regs_b);
+
+  gen_with_packet_filter : if(g_with_dpi_classifier) generate
+    U_packet_filter : ep_packet_filter
+      port map (
+        clk_sys_i  => clk_sys_i,
+        rst_n_i    => rst_n_i,
+        snk_fab_i  => fab_pipe(1),
+        snk_dreq_o => dreq_pipe(1),
+        src_fab_o  => fab_pipe(2),
+        src_dreq_i => dreq_pipe(2),
+        done_o     => pfilter_done,
+        pclass_o   => pfilter_pclass,
+        drop_o     => pfilter_drop,
+        regs_b     => regs_b);
+  end generate gen_with_packet_filter;
+
+  gen_without_packet_filter : if(not g_with_dpi_classifier) generate
+    fab_pipe(2)  <= fab_pipe(1);
+    dreq_pipe(1) <= dreq_pipe(2);
+  end generate gen_without_packet_filter;
+
   U_crc_size_checker : ep_rx_crc_size_check
     port map (
-      clk_sys_i   => clk_sys_i,
-      rst_n_i     => rst_n_i,
-      snk_fab_i   => pcs_fab_i,
-      snk_dreq_o  => pcs_dreq_o,
-      src_dreq_i  => snk_dreq,
-      src_fab_o  =>fab_int,
-      rmon_o      => rmon_o,
-      regs_b      => regs_b);
+      clk_sys_i  => clk_sys_i,
+      rst_n_i    => rst_n_i,
+      snk_fab_i  => fab_pipe(2),
+      snk_dreq_o => dreq_pipe(2),
+      src_dreq_i => dreq_pipe(3),
+      src_fab_o  => fab_pipe(3),
+      rmon_o     => rmon_o,
+      regs_b     => regs_b);
+
+
+  gen_with_vlan_unit: if(g_with_vlans) generate
+    
+  end generate gen_with_vlan_unit;
+  
 
+  fab_int <= fab_pipe(3);
+ dreq_pipe(3) <= dreq_int;
   
-  snk_dreq <= not tmp_src_i.stall;
+  dreq_int <= not tmp_src_i.stall;
 
   p_count_acks : process(clk_sys_i)
   begin
@@ -167,7 +272,7 @@ begin  -- behavioral
       else
         if(src_out_int.stb = '1' and tmp_src_i.stall = '0' and tmp_src_i.ack = '0') then
           ack_count <= ack_count + 1;
-        elsif(tmp_src_i.ack = '1' and not( src_out_int.stb = '1' and tmp_src_i.stall = '0')) then
+        elsif(tmp_src_i.ack = '1' and not(src_out_int.stb = '1' and tmp_src_i.stall = '0')) then
           ack_count <= ack_count - 1;
         end if;
         
@@ -177,16 +282,16 @@ begin  -- behavioral
 
 
   process(clk_sys_i)
-    variable stat:t_wrf_status_reg;
+    variable stat : t_wrf_status_reg;
   begin
     if rising_edge(clk_sys_i) then
       if rst_n_i = '0' then
         state           <= RXF_IDLE;
-        stb_int <= '0';
+        stb_int         <= '0';
         src_out_int.we  <= '1';
         src_out_int.adr <= c_WRF_DATA;
         src_out_int.cyc <= '0';
-        flush_stall <= '0';
+        flush_stall     <= '0';
         
       else
         case state is
@@ -194,22 +299,23 @@ begin  -- behavioral
             if(tmp_src_i.stall = '0' and fab_int.sof = '1') then
               src_out_int.cyc <= '1';
               state           <= RXF_DATA;
+              assert ematch_done = '1' report "EarlyMatchDone is 0 at SOF" severity failure;
             end if;
             
           when RXF_DATA =>
             if(tmp_src_i.stall = '0') then
-              src_out_int.dat <= fab_int.data;
-              stb_int <= fab_int.dvalid;
+              src_out_int.dat    <= fab_int.data;
+              stb_int            <= fab_int.dvalid;
               src_out_int.sel(1) <= '1';
               src_out_int.sel(0) <= not fab_int.bytesel;
             end if;
 
             if(tmp_src_i.stall = '1' and fab_int.dvalid = '1') then
-              state <= RXF_FLUSH_STALL;
+              state   <= RXF_FLUSH_STALL;
               tmp_dat <= fab_int.data;
               tmp_sel <= fab_int.bytesel;
             end if;
-            
+
             if(fab_int.eof = '1')then
               state <= RXF_FINISH_CYCLE;
             end if;
@@ -220,11 +326,11 @@ begin  -- behavioral
 
           when RXF_FLUSH_STALL =>
             if(tmp_src_i.stall = '0') then
-              src_out_int.dat <= tmp_dat;
-              stb_int <= '1';
+              src_out_int.dat    <= tmp_dat;
+              stb_int            <= '1';
               src_out_int.sel(1) <= '1';
               src_out_int.sel(0) <= not tmp_sel;
-              state <= RXF_DATA;
+              state              <= RXF_DATA;
             end if;
 
           when RXF_FINISH_CYCLE =>
@@ -243,356 +349,13 @@ begin  -- behavioral
   end process;
 
 
-  tmp_src_o.dat <= src_out_int.dat;
-  tmp_src_o.sel <= src_out_int.sel;
-  tmp_src_o.adr <= src_out_int.adr;
+  tmp_src_o.dat   <= src_out_int.dat;
+  tmp_src_o.sel   <= src_out_int.sel;
+  tmp_src_o.adr   <= src_out_int.adr;
   src_out_int.stb <= stb_int;
-  tmp_src_o.stb <= src_out_int.stb;
-  tmp_src_o.we <= src_out_int.we;
-  tmp_src_o.cyc <= src_out_int.cyc;
---  RX_FSM : process (clk_sys_i, rst_n_i)
---  begin
---    if rising_edge(clk_sys_i) then
---      if(rst_n_i = '0') then
---        state <= RXF_IDLE;
-
---        oob_ack_o <= '0';
-
---        rbuf_sof_p1_o    <= '0';
---        rbuf_eof_p1_o    <= '0';
---        rbuf_rerror_p1_o <= '0';
---        rbuf_ctrl_o      <= (others => '0');
---        rbuf_data_o      <= (others => '0');
---        rbuf_valid_o     <= '0';
---        rbuf_bytesel_o   <= '0';
-
---        rtu_rq_strobe_p1_o <= '0';
---        rtu_rq_smac_o      <= (others => '0');
---        rtu_rq_dmac_o      <= (others => '0');
---        rtu_rq_vid_o       <= (others => '0');
---        rtu_rq_has_vid_o   <= '0';
---        rtu_rq_prio_o      <= (others => '0');
---        rtu_rq_has_prio_o  <= '0';
-
---        rmon_o.rx_buffer_overrun <= '0';
---        rmon_o.rx_ok             <= '0';
---        rmon_o.rx_rtu_overrun    <= '0';
-
---        fc_pause_p_o     <= '0';
---        fc_pause_delay_o <= (others => '0');
-
---        snk_dreq_int <= '0';
---        next_hdr     <= '0';
---        is_pause     <= '1';
-
---        data_firstword <= '0';
---      else
-
---        case state is
---          when RXF_IDLE =>
-
---            oob_ack_o <= '0';
-
---            rbuf_rerror_p1_o <= '0';
---            rbuf_eof_p1_o    <= '0';
---            rbuf_valid_o     <= '0';
-
---            fc_pause_p_o <= '0';
-
---            rmon_o.rx_buffer_overrun <= '0';
---            rmon_o.rx_ok             <= '0';
---            rmon_o.rx_rtu_overrun    <= '0';
-
---            snk_dreq_int <= '1';
-
---            next_hdr       <= '0';
---            is_pause       <= '1';
---            counter        <= (others => '0');
---            data_firstword <= '1';
-
---            if(regs_b.ecr_rx_en_o = '1') then
---              if(fab_int.sof = '1') then
---                if(rbuf_drop_i = '0' and rtu_full_i = '0') then
---                  state         <= RXF_HEADER;
---                  rbuf_sof_p1_o <= '1';
---                else
---                  rmon_o.rx_buffer_overrun <= rbuf_drop_i;
---                  rmon_o.rx_rtu_overrun    <= rtu_full_i;
---                  rbuf_sof_p1_o            <= '0';
---                end if;
---              else
---                rbuf_sof_p1_o <= '0';
---              end if;
---            end if;
-
---          when RXF_HEADER =>
---            rbuf_sof_p1_o <= '0';
-
---            if(fab_int.error = '1') then
---              state <= RXF_ERROR;
---            end if;
-
---            if(rbuf_drop_i = '1') then
---              state                    <= RXF_ERROR;
---              rmon_o.rx_buffer_overrun <= '1';
---            end if;
-
---            if(fab_int.dvalid = '1' or next_hdr = '1') then
-
---              counter <= counter + 1;
-
---              case counter is
---                when x"00" =>           -- DST MAC ADDR
---                  if(fab_int.data /= x"0180") then
---                    is_pause <= '0';
---                  end if;
-
---                  rtu_rq_dmac_o(47 downto 32) <= fab_int.data;
---                  rbuf_ctrl_o                 <= c_wrsw_ctrl_dst_mac;
---                  rbuf_data_o                 <= fab_int.data;
---                  rbuf_valid_o                <= '1';
---                  snk_dreq_int                <= '1';
---                when x"01" =>
---                  if(fab_int.data /= x"c200") then
---                    is_pause <= '0';
---                  end if;
-
---                  rtu_rq_dmac_o(31 downto 16) <= fab_int.data;
---                  rbuf_ctrl_o                 <= c_wrsw_ctrl_dst_mac;
---                  rbuf_data_o                 <= fab_int.data;
---                  rbuf_valid_o                <= '1';
---                  snk_dreq_int                <= '1';
---                when x"02" =>
---                  if(fab_int.data /= x"0001") then
---                    is_pause <= '0';
---                  end if;
-
---                  rtu_rq_dmac_o(15 downto 0) <= fab_int.data;
---                  rbuf_ctrl_o                <= c_wrsw_ctrl_dst_mac;
---                  rbuf_data_o                <= fab_int.data;
---                  rbuf_valid_o               <= '1';
---                  snk_dreq_int               <= '1';
---                when x"03" =>                     -- SRC MAC ADDR
---                  rtu_rq_smac_o(47 downto 32) <= fab_int.data;
---                  rbuf_ctrl_o                 <= c_wrsw_ctrl_src_mac;
---                  rbuf_data_o                 <= fab_int.data;
---                  rbuf_valid_o                <= '1';
---                  snk_dreq_int                <= '1';
---                when x"04" =>
---                  rtu_rq_smac_o(31 downto 16) <= fab_int.data;
---                  rbuf_ctrl_o                 <= c_wrsw_ctrl_src_mac;
---                  rbuf_data_o                 <= fab_int.data;
---                  rbuf_valid_o                <= '1';
---                  snk_dreq_int                <= '1';
---                when x"05" =>
---                  rtu_rq_smac_o(15 downto 0) <= fab_int.data;
---                  rbuf_ctrl_o                <= c_wrsw_ctrl_src_mac;
---                  rbuf_data_o                <= fab_int.data;
---                  rbuf_valid_o               <= '1';
---                  snk_dreq_int               <= '0';
---                when x"06" =>                     -- ETHERTYPE
---                  if(fab_int.data = x"8808") then
---                    state        <= RXF_DATA;
---                    rbuf_data_o  <= fab_int.data;
---                    rbuf_ctrl_o  <= c_wrsw_ctrl_ethertype;
---                    rbuf_valid_o <= '1';
---                    snk_dreq_int <= '1';
---                  elsif(fab_int.data = x"8100") then  -- vlan frame
---                    is_pause <= '0';
-
----- case 1: got a VLAN-tagged frame on ACCESS port - drop it
---                    if(ep_rfcr_qmode_i = c_QMODE_PORT_ACCESS) then
---                      state        <= RXF_ERROR;
---                      rbuf_valid_o <= '0';
---                      snk_dreq_int <= '0';
---                    else
----- case 2: got a VLAN-tagged frame on a TRUNK or UNQUALIFIED port - pass it
---                      rtu_rq_has_prio_o <= '1';
---                      rtu_rq_has_vid_o  <= '1';
---                      rbuf_ctrl_o       <= c_wrsw_ctrl_none;
---                      rbuf_data_o       <= fab_int.data;
---                      snk_dreq_int      <= '1';
---                      rbuf_valid_o      <= '1';
---                    end if;
-
---                  else                  -- no vlan header
---                    rbuf_ctrl_o <= c_wrsw_ctrl_ethertype;
---                    is_pause    <= '0';
----- case 3: got a non-802.1q frame on ACCESS port: insert VLAN header
-----         with appropriate VID/PCP
---                    if(ep_rfcr_qmode_i = c_QMODE_PORT_ACCESS) then
---                      -- insert VLAN header
---                      rxdata_saved      <= fab_int.data;
---                      snk_dreq_int      <= '0';
---                      rbuf_valid_o      <= '0';
---                      rtu_rq_has_vid_o  <= '1';
---                      rtu_rq_has_prio_o <= '1';
---                      rtu_rq_vid_o      <= ep_rfcr_vid_val_i;
---                      rtu_rq_prio_o     <= ep_rfcr_prio_val_i;
---                      next_hdr          <= '1';
-
---                    elsif (ep_rfcr_qmode_i = c_QMODE_PORT_TRUNK) then
----- case 4: got a non-802.1q frame on TRUNK port: drop
-
---                      state <= RXF_ERROR;
---                    else
----- case 5: unqualified port: pass.
---                      rbuf_data_o       <= fab_int.data;
---                      rbuf_valid_o      <= '1';
---                      snk_dreq_int      <= '1';
---                      rtu_rq_has_vid_o  <= '0';
---                      rtu_rq_has_prio_o <= ep_rfcr_fix_prio_i;
---                      rtu_rq_prio_o     <= ep_rfcr_prio_val_i;
---                      state             <= RXF_DATA;
---                    end if;
-
-
---                  end if;
---                when x"07" =>           -- new ethertype
-
---                  if(ep_rfcr_qmode_i = c_QMODE_PORT_ACCESS) then  -- access:
---                                                                  -- insert
---                    snk_dreq_int <= '0';
---                    rbuf_valid_o <= '1';
---                    rbuf_ctrl_o  <= c_wrsw_ctrl_none;
---                    rbuf_data_o  <= x"8100";
---                    next_hdr     <= '1';
---                  else
---                    rbuf_ctrl_o  <= c_wrsw_ctrl_ethertype;
---                    rbuf_data_o  <= fab_int.data;
---                    rbuf_valid_o <= '1';
---                    snk_dreq_int <= '1';
---                  end if;
-
---                when x"08" =>
-
---                  if(ep_rfcr_qmode_i = c_QMODE_PORT_ACCESS) then  -- access:
---                                                                  -- insert
---                                                                  -- vlan tag
-----                    snk_dreq_int <= '0';
---                    rbuf_valid_o <= '1';
---                    rbuf_ctrl_o  <= c_wrsw_ctrl_ethertype;
---                    rbuf_data_o  <= rxdata_saved;  -- old ethertype
---                    next_hdr     <= '1';
---                  else
---                    rbuf_ctrl_o  <= c_wrsw_ctrl_vid_prio;
---                    rbuf_data_o  <= fab_int.data;
---                    rbuf_valid_o <= '1';
---                    state        <= RXF_DATA;
---                  end if;
---                  snk_dreq_int <= '1';
-
-
---                when x"09" =>
---                  rbuf_ctrl_o <= c_wrsw_ctrl_vid_prio;
---                  rbuf_data_o <= ep_rfcr_prio_val_i & '0' & ep_rfcr_vid_val_i;
-
---                  rbuf_valid_o <= '1';
---                  next_hdr     <= '0';
---                  state        <= RXF_DATA;
---                when others => null;
---              end case;
-
---            else
---              rbuf_valid_o <= '0';
---              snk_dreq_int <= '1';
---            end if;
-
---          when RXF_DATA =>
-
---            if(fab_int.error = '1') then
---              state <= RXF_ERROR;
---            end if;
-
---            if(rbuf_drop_i = '1') then
---              state                    <= RXF_ERROR;
---              rmon_o.rx_buffer_overrun <= '1';
---            end if;
-
---            rbuf_ctrl_o <= c_wrsw_ctrl_payload;
-
---            if(fab_int.eof = '1') then
-
---              if(oob_valid_i = '1' and regs_b.tscr_en_rxts_o = '1') then
---                state   <= RXF_OOB;
---                counter <= (others => '0');
---              else
---                rmon_o.rx_ok  <= '1';
---                rbuf_eof_p1_o <= '1';
---                state         <= RXF_IDLE;
---              end if;
-
---              snk_dreq_int <= '0';
-
---            end if;
-
---            -- got a valid word from the PCS
---            if(fab_int.dvalid = '1') then
-
---              if(data_firstword = '1') then
---                rtu_rq_strobe_p1_o <= not is_pause;
---                fc_pause_delay_o   <= fab_int.data;
---              -- record the PAUSE delay, it's the first 2 bytes of the payload
---              else
---                rtu_rq_strobe_p1_o <= '0';
---              end if;
-
---              data_firstword <= '0';
-
---              -- end-of-frame?
---              rbuf_data_o    <= fab_int.data;
---              rbuf_bytesel_o <= fab_int.bytesel;
---              rbuf_valid_o   <= '1';
---              snk_dreq_int   <= '1';
---            else
---              rbuf_valid_o <= '0';
---            end if;
-
---          when RXF_OOB =>
---            counter <= counter + 1;
---            if(rbuf_drop_i = '1') then
---              state                    <= RXF_ERROR;
---              rmon_o.rx_buffer_overrun <= '1';
---            else
---              case counter is
---                when x"00" =>
---                  rbuf_ctrl_o  <= c_wrsw_ctrl_rx_oob;
---                  rbuf_data_o  <= oob_data_i(47 downto 32);
---                  rbuf_valid_o <= '1';
---                when x"01" =>
---                  rbuf_ctrl_o  <= c_wrsw_ctrl_rx_oob;
---                  rbuf_data_o  <= oob_data_i(31 downto 16);
---                  rbuf_valid_o <= '1';
---                when x"02" =>
---                  rbuf_ctrl_o  <= c_wrsw_ctrl_rx_oob;
---                  rbuf_data_o  <= oob_data_i(15 downto 0);
---                  rbuf_valid_o <= '1';
---                  oob_ack_o    <= '1';
---                when x"03" =>
---                  rbuf_valid_o  <= '0';
---                  oob_ack_o     <= '0';
---                  rbuf_eof_p1_o <= '1';
---                  snk_dreq_int  <= '1';
---                  rmon_o.rx_ok  <= '1';
---                  state         <= RXF_IDLE;
-
---                when others => null;
---              end case;
---            end if;
-
---          when RXF_ERROR =>
---            fc_pause_p_o     <= '0';
---            rbuf_rerror_p1_o <= '1';
---            state            <= RXF_IDLE;
---          when others => null;
---        end case;
-
-
---      end if;
---    end if;
---  end process;
-
---  snk_dreq <= snk_dreq_int and not (fab_int.eof or fab_int.error);
+  tmp_src_o.stb   <= src_out_int.stb;
+  tmp_src_o.we    <= src_out_int.we;
+  tmp_src_o.cyc   <= src_out_int.cyc;
 
 end behavioral;
 
diff --git a/modules/wr_endpoint/ep_rx_early_address_match.vhd b/modules/wr_endpoint/ep_rx_early_address_match.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..ae43c8159e5a828efdec14f2fab5fd4725a785d0
--- /dev/null
+++ b/modules/wr_endpoint/ep_rx_early_address_match.vhd
@@ -0,0 +1,195 @@
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+
+library work;
+use work.gencores_pkg.all;              -- for gc_crc_gen
+use work.endpoint_private_pkg.all;
+use work.ep_wbgen2_pkg.all;
+
+-- 1st stage in the RX pipeline: early address matching/header parsing
+-- to filter out pause and HP frames in advance.
+
+entity ep_rx_early_address_match is
+  port(clk_sys_i : in std_logic;
+       rst_n_i   : in std_logic;
+
+       snk_fab_i  : in  t_ep_internal_fabric;
+       snk_dreq_o : out std_logic;
+
+       src_fab_o  : out t_ep_internal_fabric;
+       src_dreq_i : in  std_logic;
+
+       match_done_o         : out std_logic;
+       match_is_hp_o        : out std_logic;
+       match_is_pause_o     : out std_logic;
+       match_pause_quanta_o : out std_logic_vector(15 downto 0);
+
+       regs_b : inout t_ep_registers
+       );
+
+end ep_rx_early_address_match;
+
+architecture behavioral of ep_rx_early_address_match is
+
+  signal hdr_offset : std_logic_vector(11 downto 0);
+
+  signal at_ethertype    : std_logic;
+  signal at_vid          : std_logic;
+  signal is_tagged       : std_logic;
+  signal pause_match_int : std_logic_vector(7 downto 0);
+
+
+  signal comb_pcp_matches_hp : std_logic;
+
+  function f_compare_slv (a : std_logic_vector; b : std_logic_vector) return std_logic is
+  begin
+    if(a = b) then
+      return '1';
+    else
+      return '0';
+    end if;
+  end f_compare_slv;
+
+  signal q_in : std_logic_vector(20 downto 0);
+  signal q_out : std_logic_vector(20 downto 0);
+
+  signal q_in_valid : std_logic;
+  signal q_out_valid : std_logic;
+
+ 
+  
+begin  -- behavioral
+
+  at_ethertype <= hdr_offset(5) and snk_fab_i.dvalid and src_dreq_i;
+  at_vid       <= hdr_offset(7) and snk_fab_i.dvalid and is_tagged;
+
+  regs_b <= c_ep_registers_init_value;
+
+  q_in <= snk_fab_i.dvalid & snk_fab_i.bytesel & snk_fab_i.sof & snk_fab_i.eof & snk_fab_i.error & snk_fab_i.data;
+  q_in_valid <= snk_fab_i.eof or snk_fab_i.sof or snk_fab_i.error or snk_fab_i.dvalid;
+    
+  U_bypass_queue : ep_rx_bypass_queue
+    generic map (
+      g_size  => 16,
+      g_width => 21)
+    port map (
+      rst_n_i => rst_n_i,
+      clk_i   => clk_sys_i,
+      d_i     => q_in,
+      valid_i => q_in_valid,
+      dreq_o  => snk_dreq_o,
+      q_o     => q_out,
+      valid_o => q_out_valid,
+      dreq_i  => src_dreq_i,
+      flush_i => snk_fab_i.eof,
+      purge_i => '0');
+
+  src_fab_o.dvalid <= q_out_valid and q_out(20);
+  src_fab_o.bytesel <= q_out(19);
+  src_fab_o.sof <= q_out_valid and q_out(18);
+  src_fab_o.eof <= q_out_valid and q_out(17);
+  src_fab_o.error <= q_out_valid and q_out(16);
+
+  src_fab_o.data <= q_out(15 downto 0);
+  
+  p_hdr_offset_sreg : process(clk_sys_i)
+  begin
+    if rising_edge(clk_sys_i) then
+      if (rst_n_i = '0' or snk_fab_i.sof = '1') then
+        hdr_offset(hdr_offset'left downto 1) <= (others => '0');
+        hdr_offset(0)                        <= '1';
+      elsif(snk_fab_i.dvalid = '1') then
+        hdr_offset <= hdr_offset(hdr_offset'left-1 downto 0) & '0';
+      end if;
+    end if;
+  end process;
+
+  p_match_pause : process(clk_sys_i)
+  begin
+    if rising_edge(clk_sys_i) then
+      if rst_n_i = '0' or snk_fab_i.sof = '1' then
+        pause_match_int      <= (others => '0');
+        match_pause_quanta_o <= (others => '0');
+        match_is_pause_o     <= '0';
+      else
+        if(snk_fab_i.dvalid = '1') then
+          if(hdr_offset(0) = '1') then
+            pause_match_int (0) <= f_compare_slv(snk_fab_i.data, x"0180");
+          end if;
+          if(hdr_offset(1) = '1') then
+            pause_match_int (1) <= f_compare_slv(snk_fab_i.data, x"c200");
+          end if;
+          if(hdr_offset(2) = '1') then
+            pause_match_int (2) <= f_compare_slv(snk_fab_i.data, x"0001");
+          end if;
+          if(hdr_offset(3) = '1') then
+            pause_match_int (3) <= f_compare_slv(snk_fab_i.data, regs_b.mach_o);
+          end if;
+          if(hdr_offset(4) = '1') then
+            pause_match_int (4) <= f_compare_slv(snk_fab_i.data, regs_b.macl_o(31 downto 16));
+          end if;
+          if(hdr_offset(5) = '1') then
+            pause_match_int (5) <= f_compare_slv(snk_fab_i.data, regs_b.macl_o(15 downto 0));
+          end if;
+          if(hdr_offset(6) = '1') then
+            pause_match_int (6) <= f_compare_slv(snk_fab_i.data, x"8808");
+          end if;
+          if(hdr_offset(7) = '1') then
+            pause_match_int (7) <= f_compare_slv(snk_fab_i.data, x"0001");
+          end if;
+          if(hdr_offset(8) = '1') then
+            match_is_pause_o     <= f_compare_slv(pause_match_int, x"ff");
+            match_pause_quanta_o <= snk_fab_i.data;
+          end if;
+        end if;
+      end if;
+    end if;
+  end process;
+
+  p_match_hp : process(clk_sys_i)
+    variable index : integer;
+  begin
+    
+    if rising_edge(clk_sys_i) then
+      index := to_integer(unsigned(snk_fab_i.data(15 downto 13)));
+
+      if rst_n_i = '0' or snk_fab_i.sof = '1' then
+        is_tagged     <= '0';
+        match_is_hp_o <= '0';
+      else
+        if(at_ethertype = '1') then
+          is_tagged <= f_compare_slv(snk_fab_i.data, x"8100");
+        end if;
+
+        if (at_vid = '1') then
+          if(regs_b.rfcr_a_hp_o = '1' and regs_b.rfcr_hpap_o(index) = '1') then
+            match_is_hp_o <= '1';
+          else
+            match_is_hp_o <= '0';
+          end if;
+        end if;
+      end if;
+    end if;
+  end process;
+
+  p_gen_done : process(clk_sys_i)
+  begin
+    if rising_edge(clk_sys_i) then
+      if rst_n_i = '0' or snk_fab_i.sof = '1' then
+        match_done_o <= '0';
+      else
+        if hdr_offset(8) = '1' then
+          match_done_o <= '1';
+        end if;
+      end if;
+    end if;
+  end process;
+
+
+
+end behavioral;
+
+
+
+
diff --git a/modules/wr_endpoint/ep_wishbone_controller.vhd b/modules/wr_endpoint/ep_wishbone_controller.vhd
index 7a7eb8ed42d99732c28ca5824cf91d3d34aa0b67..a5daef5090a189c6a0c9c155b580fdc318c074f9 100644
--- a/modules/wr_endpoint/ep_wishbone_controller.vhd
+++ b/modules/wr_endpoint/ep_wishbone_controller.vhd
@@ -3,7 +3,7 @@
 ---------------------------------------------------------------------------------------
 -- File           : ep_wishbone_controller.vhd
 -- Author         : auto-generated by wbgen2 from ep_wishbone_controller.wb
--- Created        : Mon Aug 22 16:14:10 2011
+-- Created        : Mon Aug 22 23:38:16 2011
 -- Standard       : VHDL'87
 ---------------------------------------------------------------------------------------
 -- THIS FILE WAS GENERATED BY wbgen2 FROM SOURCE FILE ep_wishbone_controller.wb
@@ -65,6 +65,7 @@ signal ep_rfcr_a_runt_int                       : std_logic      ;
 signal ep_rfcr_a_giant_int                      : std_logic      ;
 signal ep_rfcr_a_hp_int                         : std_logic      ;
 signal ep_rfcr_keep_crc_int                     : std_logic      ;
+signal ep_rfcr_hpap_int                         : std_logic_vector(7 downto 0);
 signal ep_rfcr_mru_int                          : std_logic_vector(13 downto 0);
 signal ep_vcr0_qmode_int                        : std_logic_vector(1 downto 0);
 signal ep_vcr0_fix_prio_int                     : std_logic      ;
@@ -129,6 +130,7 @@ begin
     ep_rfcr_a_giant_int <= '0';
     ep_rfcr_a_hp_int <= '0';
     ep_rfcr_keep_crc_int <= '0';
+    ep_rfcr_hpap_int <= "00000000";
     ep_rfcr_mru_int <= "00000000000000";
     ep_vcr0_qmode_int <= "00";
     ep_vcr0_fix_prio_int <= '0';
@@ -273,21 +275,15 @@ begin
               ep_rfcr_a_giant_int <= wrdata_reg(1);
               ep_rfcr_a_hp_int <= wrdata_reg(2);
               ep_rfcr_keep_crc_int <= wrdata_reg(3);
-              ep_rfcr_mru_int <= wrdata_reg(17 downto 4);
+              ep_rfcr_hpap_int <= wrdata_reg(11 downto 4);
+              ep_rfcr_mru_int <= wrdata_reg(25 downto 12);
             else
               rddata_reg(0) <= ep_rfcr_a_runt_int;
               rddata_reg(1) <= ep_rfcr_a_giant_int;
               rddata_reg(2) <= ep_rfcr_a_hp_int;
               rddata_reg(3) <= ep_rfcr_keep_crc_int;
-              rddata_reg(17 downto 4) <= ep_rfcr_mru_int;
-              rddata_reg(18) <= 'X';
-              rddata_reg(19) <= 'X';
-              rddata_reg(20) <= 'X';
-              rddata_reg(21) <= 'X';
-              rddata_reg(22) <= 'X';
-              rddata_reg(23) <= 'X';
-              rddata_reg(24) <= 'X';
-              rddata_reg(25) <= 'X';
+              rddata_reg(11 downto 4) <= ep_rfcr_hpap_int;
+              rddata_reg(25 downto 12) <= ep_rfcr_mru_int;
               rddata_reg(26) <= 'X';
               rddata_reg(27) <= 'X';
               rddata_reg(28) <= 'X';
@@ -759,6 +755,8 @@ regs_b.rfcr_a_giant_o <= ep_rfcr_a_giant_int;
 regs_b.rfcr_a_hp_o <= ep_rfcr_a_hp_int;
 -- RX keep CRC
 regs_b.rfcr_keep_crc_o <= ep_rfcr_keep_crc_int;
+-- RX Fiter HP Priorities
+regs_b.rfcr_hpap_o <= ep_rfcr_hpap_int;
 -- Maximum receive unit (MRU)
 regs_b.rfcr_mru_o <= ep_rfcr_mru_int;
 -- RX 802.1q port mode