diff --git a/libraries/technology/tse/hdllib.cfg b/libraries/technology/tse/hdllib.cfg
index 5b71fe5191e51bac29016fed57641fab7f0cfcc8..86bd3ec8218f5f562c477a4dde02f407d2a573b8 100644
--- a/libraries/technology/tse/hdllib.cfg
+++ b/libraries/technology/tse/hdllib.cfg
@@ -29,16 +29,20 @@ synth_files =
     tech_tse_arria10_e1sg.vhd
     tech_tse_arria10_e2sg.vhd
     tech_tse.vhd
+    tech_tse_setup.vhd
+    tech_tse_with_setup.vhd
     tb_tech_tse_pkg.vhd
 
 test_bench_files =
     sim_tse.vhd
     tb_tech_tse_pkg.vhd
     tb_tech_tse.vhd
+    tb_tech_tse_with_setup.vhd
     tb_tb_tech_tse.vhd
 
 regression_test_vhdl = 
     tb_tb_tech_tse.vhd
+    tb_tech_tse_with_setup.vhd
 
 
 [modelsim_project_file]
diff --git a/libraries/technology/tse/tb_tech_tse_with_setup.vhd b/libraries/technology/tse/tb_tech_tse_with_setup.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..988214e6568cbbce51a166b5b883b624f09c93ae
--- /dev/null
+++ b/libraries/technology/tse/tb_tech_tse_with_setup.vhd
@@ -0,0 +1,308 @@
+-------------------------------------------------------------------------------
+--
+-- Copyright (C) 2009
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- This program is free software: you can redistribute it and/or modify
+-- it under the terms of the GNU General Public License as published by
+-- the Free Software Foundation, either version 3 of the License, or
+-- (at your option) any later version.
+--
+-- This program is distributed in the hope that it will be useful,
+-- but WITHOUT ANY WARRANTY; without even the implied warranty of
+-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+-- GNU General Public License for more details.
+--
+-- You should have received a copy of the GNU General Public License
+-- along with this program.  If not, see <http://www.gnu.org/licenses/>.
+--
+-------------------------------------------------------------------------------
+
+-- Purpose: Testbench for tech_tse for the Tripple Speed Ethernet IP technology
+--          wrapper, with setup.
+-- Description:
+--   Same tb as tb_tech_tse.vhd, but instead:
+--   . fixed use TSE IP (c_sim_level = 0)
+--   . using TSE setup in DUT
+--   . verify external MM access to TSE after setup in p_mm_setup.
+--   . use c_jumbo_en = FALSE for maximum 1500 packet size as with unb_osy, a
+--     9000 octet packet is received properly, but has rx_src_out.err = 3
+--     indicating invalid length. Use c_jumbo_en = TRUE to avoid invalid
+--     length.
+-- Usage:
+--   > as 10
+--   > run -all
+
+LIBRARY IEEE, technology_lib, common_lib, dp_lib;
+USE IEEE.std_logic_1164.ALL;
+USE IEEE.numeric_std.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.common_mem_pkg.ALL;
+USE common_lib.common_network_layers_pkg.ALL;
+USE common_lib.common_network_total_header_pkg.ALL;
+USE common_lib.tb_common_pkg.ALL;
+USE common_lib.tb_common_mem_pkg.ALL;
+USE dp_lib.dp_stream_pkg.ALL;
+USE technology_lib.technology_pkg.ALL;
+USE technology_lib.technology_select_pkg.ALL;
+USE WORK.tech_tse_pkg.ALL;
+USE WORK.tb_tech_tse_pkg.ALL;
+
+
+ENTITY tb_tech_tse_with_setup IS
+  -- Test bench control parameters
+  GENERIC (
+    g_technology : NATURAL := c_tech_select_default;
+    --   g_data_type = c_tb_tech_tse_data_type_symbols  = 0
+    --   g_data_type = c_tb_tech_tse_data_type_counter  = 1
+    g_data_type  : NATURAL := c_tb_tech_tse_data_type_symbols;
+    g_tb_end     : BOOLEAN := TRUE  -- when TRUE then tb_end ends this simulation, else a higher multi-testbench will end the simulation
+  );
+  PORT (
+    tb_end : OUT STD_LOGIC
+  );
+END tb_tech_tse_with_setup;
+
+
+ARCHITECTURE tb OF tb_tech_tse_with_setup IS
+
+  CONSTANT c_sim                : BOOLEAN := TRUE;
+  CONSTANT c_sim_level          : NATURAL := 0;    -- 0 = use IP; 1 = use fast serdes model;
+  CONSTANT c_jumbo_en           : BOOLEAN := TRUE;
+
+  CONSTANT sys_clk_period       : TIME := 10 ns;  -- 100 MHz
+  CONSTANT eth_clk_period       : TIME :=  8 ns;  -- 125 MHz
+  CONSTANT cable_delay          : TIME := sel_a_b(c_sim_level=0, 12 ns, 0 ns);
+
+  CONSTANT c_promis_en          : BOOLEAN := FALSE;
+  CONSTANT c_tx_ready_latency   : NATURAL := c_tech_tse_tx_ready_latency;  -- 0, 1 are supported, must match TSE MAC c_tech_tse_tx_ready_latency
+  CONSTANT c_nof_tx_not_valid   : NATURAL := 0;  -- when > 0 then pull tx valid low for c_nof_tx_not_valid beats during tx
+
+  --CONSTANT c_pkt_length_arr     : t_nat_natural_arr := (0, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 1472, 1473, 9000);
+  CONSTANT c_pkt_length_arr     : t_nat_natural_arr := array_init(0, 80, 1) & array_init(1499, 2, 1) & 9000;
+  CONSTANT c_nof_pkt            : NATURAL := c_pkt_length_arr'LENGTH;
+  
+  CONSTANT c_dst_mac            : STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE) := X"10FA01020300";
+  CONSTANT c_src_mac            : STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE) := X"123456789ABC";  -- = 12-34-56-78-9A-BC
+  CONSTANT c_ethertype          : STD_LOGIC_VECTOR(c_network_eth_type_slv'RANGE) := X"10FA";
+  CONSTANT c_etherlen           : STD_LOGIC_VECTOR(c_network_eth_type_slv'RANGE) := "0000000000010000";
+
+  -- Packet headers
+  CONSTANT c_eth_header_loopback : t_network_eth_header := (c_src_mac, c_src_mac, c_ethertype);
+  CONSTANT c_eth_header_etherlen : t_network_eth_header := (c_src_mac, c_src_mac, c_etherlen);
+  
+  SIGNAL total_header_loopback   : t_network_total_header;
+  SIGNAL total_header_etherlen   : t_network_total_header;
+  
+  -- Clocks and reset
+  SIGNAL rx_end            : STD_LOGIC := '0';
+  SIGNAL eth_clk           : STD_LOGIC := '0';  -- tse reference clock
+  SIGNAL sys_clk           : STD_LOGIC := '0';  -- system clock
+  SIGNAL st_clk            : STD_LOGIC;         -- stream clock
+  SIGNAL mm_clk            : STD_LOGIC;         -- memory-mapped bus clock
+  SIGNAL mm_rst            : STD_LOGIC;         -- reset synchronous with mm_clk
+
+  -- TSE MAC control interface
+  SIGNAL tse_setup_done    : STD_LOGIC;
+
+  SIGNAL mm_init           : STD_LOGIC := '1';
+  SIGNAL mm_copi           : t_mem_copi;
+  SIGNAL mm_cipo           : t_mem_cipo;
+  SIGNAL mm_rddata         : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);  -- for view in Wave window
+
+  -- TSE MAC transmit interface
+  -- . The tb is the ST source
+  SIGNAL tx_en             : STD_LOGIC := '1';
+  SIGNAL tx_siso           : t_dp_siso;
+  SIGNAL tx_sosi           : t_dp_sosi;
+  -- . MAC specific
+  SIGNAL tx_mac_in         : t_tech_tse_tx_mac;
+  SIGNAL tx_mac_out        : t_tech_tse_tx_mac;
+
+  -- TSE MAC receive interface
+  -- . The tb is the ST sink
+  SIGNAL rx_sosi           : t_dp_sosi;
+  SIGNAL rx_siso           : t_dp_siso;
+  SIGNAL rx_data           : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);  -- for view in Wave window
+  -- . MAC specific
+  SIGNAL rx_mac_out        : t_tech_tse_rx_mac;
+
+  -- TSE PHY interface
+  SIGNAL eth_txp           : STD_LOGIC;
+  SIGNAL eth_rxp           : STD_LOGIC;
+
+  SIGNAL tse_led           : t_tech_tse_led;
+
+  -- Verification
+  SIGNAL tx_pkt_cnt     : NATURAL := 0;
+  SIGNAL rx_pkt_cnt     : NATURAL := 0;
+  
+BEGIN
+
+  eth_clk <= NOT eth_clk AFTER eth_clk_period/2;  -- TSE reference clock
+  sys_clk <= NOT sys_clk AFTER sys_clk_period/2;  -- System clock
+
+  mm_clk  <= sys_clk;
+  st_clk  <= sys_clk;
+  
+  -- Use signal to leave unused fields 'X'
+  total_header_loopback.eth <= c_eth_header_loopback;
+  total_header_etherlen.eth <= c_eth_header_etherlen;
+
+  mm_rddata <= mm_cipo.rddata(c_word_w-1 DOWNTO 0);
+  rx_data <= rx_sosi.data(c_word_w-1 DOWNTO 0);
+
+  p_mm_setup : PROCESS
+  BEGIN
+    mm_init <= '1';
+    mm_copi.wr <= '0';
+    mm_copi.rd <= '0';
+
+    -- reset release
+    mm_rst <= '1';
+    FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(mm_clk); END LOOP;
+    mm_rst <= '0';
+    FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(mm_clk); END LOOP;
+
+    -- Wait for tech_tse_with_setup to finish MM access to TSE
+    proc_common_wait_until_high(mm_clk, tse_setup_done);
+    proc_common_wait_some_cycles(mm_clk, 10);
+
+    -- Verify external MM access to TSE
+    proc_mem_mm_bus_rd(16#000#, mm_clk, mm_cipo, mm_copi);  -- REV --> CUST_VERSION & 0x0901, 0x1304
+    ASSERT UNSIGNED(mm_rddata(c_16-1 DOWNTO 0)) = X"1304" REPORT "Wrong external MM read access result." SEVERITY ERROR;
+
+    -- Wait for link synchronisation
+    proc_common_wait_until_high(mm_clk, tse_led.link);
+    proc_common_wait_some_cycles(mm_clk, 10);
+
+    mm_init <= '0';
+    WAIT;
+  END PROCESS;
+
+  
+  p_ff_transmitter : PROCESS
+  BEGIN
+    -- . Avalon ST
+    tx_sosi.data  <= (OTHERS=>'0');
+    tx_sosi.valid <= '0';
+    tx_sosi.sop   <= '0';
+    tx_sosi.eop   <= '0';
+    tx_sosi.empty <= (OTHERS=>'0');
+    tx_sosi.err   <= (OTHERS=>'0');
+    -- . MAC specific
+    tx_mac_in.crc_fwd <= '0';  -- when '0' then TSE MAC generates the TX CRC field
+
+    WHILE mm_init/='0' LOOP
+      WAIT UNTIL rising_edge(st_clk);
+    END LOOP;
+    FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(st_clk); END LOOP;
+
+    -- Loopback txp->rxp so DST_MAC = c_src_mac to send to itself
+    
+    -- TX frame:
+    -- . I=0 is empty payload, so only 4 words of the ETH header with 46 padding zeros, so empty = 2
+    -- . For I=1 to 46 the payload length remains 46 with padding zeros, so empty = 2
+    -- . For I>46 the payload length is I and empty = 4 - (I mod 4)
+    
+    FOR I IN 0 TO c_nof_pkt-1 LOOP
+      proc_tech_tse_tx_packet(total_header_loopback, c_pkt_length_arr(I), g_data_type, c_tx_ready_latency, c_nof_tx_not_valid, st_clk, tx_en, tx_siso, tx_sosi);
+    END LOOP;
+
+    FOR I IN 0 TO 1500 * 2 LOOP WAIT UNTIL rising_edge(st_clk); END LOOP;
+    rx_end <= '1';
+    WAIT;
+  END PROCESS;
+
+  
+  p_ff_receiver : PROCESS
+  BEGIN
+    -- . Avalon ST
+    rx_siso.ready <= '0';
+
+    WHILE mm_init/='0' LOOP
+      WAIT UNTIL rising_edge(st_clk);
+    END LOOP;
+
+    -- Receive forever
+    WHILE TRUE LOOP
+      proc_tech_tse_rx_packet(total_header_loopback, g_data_type, st_clk, rx_sosi, rx_siso);
+    END LOOP;
+
+    WAIT;
+  END PROCESS;
+
+  
+  dut : ENTITY work.tech_tse_with_setup
+  GENERIC MAP (
+    g_technology => g_technology,
+    g_ETH_PHY    => "LVDS",  -- "LVDS" (default): uses LVDS IOs for ctrl_unb_common, "XCVR": uses tranceiver PHY
+    g_jumbo_en   => c_jumbo_en,
+    g_sim        => c_sim,
+    g_sim_level  => c_sim_level     -- 0 = use IP; 1 = use fast serdes model;
+  )
+  PORT MAP (
+    -- Clocks and reset
+    mm_rst         => mm_rst,
+    mm_clk         => mm_clk,
+    eth_clk        => eth_clk,
+    tx_snk_clk     => st_clk,
+    rx_src_clk     => st_clk,
+
+    -- TSE setup
+    src_mac        => c_src_mac,
+    setup_done     => tse_setup_done,
+    
+    -- Memory Mapped Slave
+    mm_ctlr_copi   => mm_copi,
+    mm_ctlr_cipo   => mm_cipo,
+    
+    -- MAC transmit interface
+    -- . ST sink
+    tx_snk_in      => tx_sosi,
+    tx_snk_out     => tx_siso,
+    
+    -- MAC receive interface
+    -- . ST Source
+    rx_src_in      => rx_siso,
+    rx_src_out     => rx_sosi,
+
+    -- PHY interface
+    eth_txp        => eth_txp,
+    eth_rxp        => eth_rxp,
+
+    tse_led        => tse_led
+  );
+
+  -- Loopback
+  eth_rxp <= TRANSPORT eth_txp AFTER cable_delay;
+
+  -- Verification
+  tx_pkt_cnt <= tx_pkt_cnt + 1 WHEN tx_sosi.sop='1' AND rising_edge(st_clk);
+  rx_pkt_cnt <= rx_pkt_cnt + 1 WHEN rx_sosi.eop='1' AND rising_edge(st_clk);
+  
+  p_verify : PROCESS
+  BEGIN
+    tb_end <= '0';
+    WAIT UNTIL rx_end='1';
+    -- Verify that all transmitted packets have been received
+    IF tx_pkt_cnt=0 THEN
+      REPORT "No packets were transmitted." SEVERITY ERROR;
+    ELSIF rx_pkt_cnt=0 THEN
+      REPORT "No packets were received." SEVERITY ERROR;
+    ELSIF tx_pkt_cnt/=rx_pkt_cnt THEN
+      REPORT "Not all transmitted packets were received." SEVERITY ERROR;
+    END IF;
+    tb_end <= '1';
+    
+    WAIT FOR 1 ns;
+    IF g_tb_end=FALSE THEN
+      REPORT "Tb simulation finished." SEVERITY NOTE;
+    ELSE
+      REPORT "Tb simulation finished." SEVERITY FAILURE;
+    END IF;
+    WAIT;
+  END PROCESS;
+  
+END tb;
diff --git a/libraries/technology/tse/tech_tse_setup.vhd b/libraries/technology/tse/tech_tse_setup.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..fc02da2dc47117ca8647e27f75e60cd68577433b
--- /dev/null
+++ b/libraries/technology/tse/tech_tse_setup.vhd
@@ -0,0 +1,259 @@
+-------------------------------------------------------------------------------
+--
+-- Copyright 2022
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- Licensed under the Apache License, Version 2.0 (the "License");
+-- you may not use this file except in compliance with the License.
+-- You may obtain a copy of the License at
+--
+--     http://www.apache.org/licenses/LICENSE-2.0
+--
+-- Unless required by applicable law or agreed to in writing, software
+-- distributed under the License is distributed on an "AS IS" BASIS,
+-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+-- See the License for the specific language governing permissions and
+-- limitations under the License.
+--
+-------------------------------------------------------------------------------
+-- AUthor: E. Kooistra
+-- Purpose: Set up TSE via MM
+-- Description:
+-- . TSE set up as in tb_tech_tse_pkg, unb_osy/unbos_eth.c and
+--   eth1g_master.vhd. Cannot use proc_mem_mm_bus_*() because a synthesis
+--   process can only have one rising_edge(mm_clk) statement
+-- . After tse_init is done, then connect to external MM controller, to allow
+--   external  monitoring of the TSE.
+
+LIBRARY IEEE, common_lib, dp_lib;
+USE IEEE.std_logic_1164.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.common_mem_pkg.ALL;
+USE work.tech_tse_pkg.ALL;
+
+ENTITY tech_tse_setup IS
+  GENERIC (
+    g_sim : BOOLEAN;
+    -- Nios 1GbE-I uses ETH_FRAME_LENGTH = 1518 in inbos_eth.h. Use g_jumbo_en
+    -- = FALSE for frame_len <= 1500 octets. If frame is longer then this
+    -- yields invalid length flag in rx_sosi.err, but data is still received.
+    -- Use g_jumbo_en = TRUE for frame_len <= 9000 octets (jumbo frames).
+    g_jumbo_en : BOOLEAN := FALSE
+  );
+  PORT (
+    -- Clocks and reset
+    mm_rst         : IN  STD_LOGIC;
+    mm_clk         : IN  STD_LOGIC;
+    
+    -- TSE setup
+    src_mac        : IN STD_LOGIC_VECTOR(c_48-1 DOWNTO 0);
+    setup_done     : OUT STD_LOGIC;
+
+    -- Memory Mapped Peripheral
+    -- . Controller side
+    mm_ctlr_copi   : IN  t_mem_copi;
+    mm_ctlr_cipo   : OUT t_mem_cipo;
+    -- . Peripheral side
+    mm_peri_copi   : OUT t_mem_copi;
+    mm_peri_cipo   : IN  t_mem_cipo
+  );
+END tech_tse_setup;
+
+ARCHITECTURE rtl OF tech_tse_setup IS
+
+  -- FALSE receive only frames for this src_mac and broadcast, TRUE receive all
+  CONSTANT c_promis_en  : BOOLEAN := FALSE;
+
+  -- Access the MM bus
+  TYPE t_state IS (s_rd_pcs_rev, s_wr_if_mode, s_rd_control, s_rd_status, s_wr_control,
+                   s_rd_mac_rev, s_wr_promis_en, s_wr_mac_0, s_wr_mac_1, s_wr_tx_ipg_len, s_wr_frm_len,
+                   s_wr_rx_section_empty, s_wr_rx_section_full, s_wr_tx_section_empty, s_wr_tx_section_full,
+                   s_wr_rx_almost_empty, s_wr_rx_almost_full, s_wr_tx_almost_empty, s_wr_tx_almost_full,
+                   s_rd_tx_cmd_stat, s_rd_rx_cmd_stat,
+                   s_done);
+
+  SIGNAL state           : t_state;
+  SIGNAL next_state      : t_state;
+  SIGNAL psc_access      : STD_LOGIC;  -- active during PCS registers access, for view in Wave window
+  SIGNAL fifo_access     : STD_LOGIC;  -- active during FIFO registers access, for view in Wave window
+
+  -- Memory Mapped Slave
+  SIGNAL tse_init        : STD_LOGIC := '1';
+  SIGNAL tse_ctlr_copi   : t_mem_copi;
+  SIGNAL tse_ctlr_cipo   : t_mem_cipo;
+  SIGNAL tse_waitrequest : STD_LOGIC;
+  SIGNAL tse_wrdata      : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);  -- for view in Wave window
+  SIGNAL tse_rddata      : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);  -- for view in Wave window
+
+  SIGNAL src_mac_0       : STD_LOGIC_VECTOR(c_32-1 DOWNTO 0);
+  SIGNAL src_mac_1       : STD_LOGIC_VECTOR(c_16-1 DOWNTO 0);
+
+BEGIN
+
+  setup_done <= NOT tse_init;
+
+  src_mac_0 <= hton(src_mac(c_48-1 DOWNTO c_16), 4);
+  src_mac_1 <= hton(src_mac(c_16-1 DOWNTO  0), 2);
+
+  -- Select MM interface controller
+  --               ___
+  --              |   |
+  --  mm_ctlr ----| 0 |
+  --              |   |---- mm_peri
+  -- tse_ctlr ----| 1 |
+  --              |___|
+  --                |
+  -- tse_init ------/
+  --
+  mm_peri_copi <= tse_ctlr_copi  WHEN tse_init = '1' ELSE mm_ctlr_copi;
+  mm_ctlr_cipo <= c_mem_cipo_rst WHEN tse_init = '1' ELSE mm_peri_cipo;
+  tse_ctlr_cipo <= mm_peri_cipo;
+  tse_waitrequest <= tse_ctlr_cipo.waitrequest;
+  tse_wrdata <= tse_ctlr_copi.wrdata(c_word_w-1 DOWNTO 0);
+  tse_rddata <= tse_ctlr_cipo.rddata(c_word_w-1 DOWNTO 0);
+
+  p_state : PROCESS(mm_rst, mm_clk)
+  BEGIN
+    IF mm_rst = '1' THEN
+      state <= s_rd_pcs_rev;
+      next_state <= s_rd_pcs_rev;
+      tse_init <= '1';
+      tse_ctlr_copi <= c_mem_copi_rst;
+      psc_access <= '0';
+      fifo_access <= '0';
+    ELSIF rising_edge(mm_clk) THEN
+      tse_init <= '1';
+      psc_access <= '0';
+      fifo_access <= '0';
+
+      -- Issue MM access
+      CASE state IS
+        -- PSC control
+        WHEN s_rd_pcs_rev =>
+          psc_access <= '1';
+          proc_mem_bus_rd(func_tech_tse_map_pcs_addr(16#22#), tse_ctlr_copi);  -- REV --> 0x0901, 0x1304
+          next_state <= s_wr_if_mode;
+
+        WHEN s_wr_if_mode =>
+          psc_access <= '1';
+          proc_mem_bus_wr(func_tech_tse_map_pcs_addr(16#28#), 16#0008#, tse_ctlr_copi);  -- IF_MODE <-- Force 1GbE,
+          next_state <= s_rd_control;
+
+        WHEN s_rd_control =>
+          psc_access <= '1';
+          proc_mem_bus_rd(func_tech_tse_map_pcs_addr(16#00#), tse_ctlr_copi);  -- CONTROL --> 0x1140
+          next_state <= s_rd_status;
+
+        WHEN s_rd_status =>
+          psc_access <= '1';
+          proc_mem_bus_rd(func_tech_tse_map_pcs_addr(16#02#), tse_ctlr_copi);  -- STATUS --> 0x000D
+          next_state <= s_wr_control;
+
+        WHEN s_wr_control =>
+          psc_access <= '1';
+          IF g_sim = FALSE THEN
+            proc_mem_bus_wr(func_tech_tse_map_pcs_addr(16#00#), 16#1140#, tse_ctlr_copi);  -- CONTROL <-- Keep auto negotiate enabled (is reset default)
+          ELSE
+            proc_mem_bus_wr(func_tech_tse_map_pcs_addr(16#00#), 16#0140#, tse_ctlr_copi);  -- CONTROL <-- In simulation disable auto negotiate
+          END IF;
+          next_state <= s_rd_mac_rev;
+
+        -- MAC control
+        WHEN s_rd_mac_rev =>
+          proc_mem_bus_rd(16#000#, tse_ctlr_copi);  -- REV --> CUST_VERSION & 0x0901
+          next_state <= s_wr_promis_en;
+
+        WHEN s_wr_promis_en =>
+          IF c_promis_en = FALSE THEN
+            proc_mem_bus_wr(16#008#, 16#0100004B#, tse_ctlr_copi);  -- COMMAND_CONFIG
+          ELSE
+            proc_mem_bus_wr(16#008#, 16#0100005B#, tse_ctlr_copi);
+          END IF;
+          next_state <= s_wr_mac_0;
+
+        WHEN s_wr_mac_0 =>
+          proc_mem_bus_wr(16#00C#, src_mac_0, tse_ctlr_copi);  -- MAC_0
+          next_state <= s_wr_mac_1;
+
+        WHEN s_wr_mac_1 =>
+          proc_mem_bus_wr(16#010#, src_mac_1, tse_ctlr_copi);  -- MAC_1 <-- SRC_MAC
+          next_state <= s_wr_tx_ipg_len;
+
+        WHEN s_wr_tx_ipg_len =>
+          proc_mem_bus_wr(16#05C#, 16#0000000C#, tse_ctlr_copi);  -- TX_IPG_LENGTH <-- interpacket gap = 12
+          next_state <= s_wr_frm_len;
+
+        WHEN s_wr_frm_len =>
+          IF g_jumbo_en = FALSE THEN
+            proc_mem_bus_wr(16#014#, 16#000005EE#, tse_ctlr_copi);  -- FRM_LENGTH <-- receive max frame length = 1518
+          ELSE
+            proc_mem_bus_wr(16#014#, 16#0000233A#, tse_ctlr_copi);  -- FRM_LENGTH <-- receive max frame length = 9018
+          END IF;
+          next_state <= s_wr_rx_section_empty;
+
+        -- MAC FIFO
+        WHEN s_wr_rx_section_empty =>
+          fifo_access <= '1';
+          proc_mem_bus_wr(16#01C#, c_tech_tse_rx_fifo_depth-16, tse_ctlr_copi);  -- RX_SECTION_EMPTY <-- default FIFO depth - 16, >3
+          next_state <= s_wr_rx_section_full;
+
+        WHEN s_wr_rx_section_full =>
+          fifo_access <= '1';
+          proc_mem_bus_wr(16#020#, 16, tse_ctlr_copi);  -- RX_SECTION_FULL <-- default 16
+          next_state <= s_wr_tx_section_empty;
+
+        WHEN s_wr_tx_section_empty =>
+          fifo_access <= '1';
+          proc_mem_bus_wr(16#024#, c_tech_tse_tx_fifo_depth-16, tse_ctlr_copi);  -- TX_SECTION_EMPTY <-- default FIFO depth - 16, >3
+          next_state <= s_wr_tx_section_full;
+
+        WHEN s_wr_tx_section_full =>
+          fifo_access <= '1';
+          proc_mem_bus_wr(16#028#, 16, tse_ctlr_copi);  -- TX_SECTION_FULL <-- default 16, >~ 8 otherwise no tx
+          next_state <= s_wr_rx_almost_empty;
+
+        WHEN s_wr_rx_almost_empty =>
+          fifo_access <= '1';
+          proc_mem_bus_wr(16#02C#, 8, tse_ctlr_copi);  -- RX_ALMOST_EMPTY <-- default 8
+          next_state <= s_wr_rx_almost_full;
+
+        WHEN s_wr_rx_almost_full =>
+          fifo_access <= '1';
+          proc_mem_bus_wr(16#030#, 8, tse_ctlr_copi);  -- RX_ALMOST_FULL <-- default 8
+          next_state <= s_wr_tx_almost_empty;
+
+        WHEN s_wr_tx_almost_empty =>
+          fifo_access <= '1';
+          proc_mem_bus_wr(16#034#, 8, tse_ctlr_copi);  -- TX_ALMOST_EMPTY  <-- default 8
+          next_state <= s_wr_tx_almost_full;
+
+        WHEN s_wr_tx_almost_full =>
+          fifo_access <= '1';
+          proc_mem_bus_wr(16#038#, c_tech_tse_tx_ready_latency + 3, tse_ctlr_copi);   -- TX_ALMOST_FULL   <-- default 3
+          next_state <= s_rd_tx_cmd_stat;
+
+        -- MAC status
+        WHEN s_rd_tx_cmd_stat =>
+          proc_mem_bus_rd(16#0E8#, tse_ctlr_copi);   -- TX_CMD_STAT --> 0x00040000 : [18]=1 TX_SHIFT16, [17]=0 OMIT_CRC
+          next_state <= s_rd_rx_cmd_stat;
+
+        WHEN s_rd_rx_cmd_stat =>
+          proc_mem_bus_rd(16#0EC#, tse_ctlr_copi);   -- RX_CMD_STAT --> 0x02000000 : [25]=1 RX_SHIFT16
+          next_state <= s_done;
+
+        WHEN OTHERS =>  -- s_done
+          tse_init <= '0';
+      END CASE;
+
+      -- Go to next state when MM access was accepted
+      IF state /= next_state AND tse_waitrequest = '0' THEN
+        tse_ctlr_copi.wr <= '0';
+        tse_ctlr_copi.rd <= '0';
+        state <= next_state;
+      END IF;
+
+    END IF;
+  END PROCESS;
+
+END ARCHITECTURE;
diff --git a/libraries/technology/tse/tech_tse_with_setup.vhd b/libraries/technology/tse/tech_tse_with_setup.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..41173fa0a9df5c51c9e9a618d751bfb88fed9e2b
--- /dev/null
+++ b/libraries/technology/tse/tech_tse_with_setup.vhd
@@ -0,0 +1,173 @@
+-------------------------------------------------------------------------------
+--
+-- Copyright 2022
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- Licensed under the Apache License, Version 2.0 (the "License");
+-- you may not use this file except in compliance with the License.
+-- You may obtain a copy of the License at
+--
+--     http://www.apache.org/licenses/LICENSE-2.0
+--
+-- Unless required by applicable law or agreed to in writing, software
+-- distributed under the License is distributed on an "AS IS" BASIS,
+-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+-- See the License for the specific language governing permissions and
+-- limitations under the License.
+--
+-------------------------------------------------------------------------------
+-- AUthor: E. Kooistra
+-- Purpose: Instantiate and setup TSE via MM
+-- Description:
+-- . Based on tech_tse instance in eth.vhd
+-- . Set up TSE in state machnine and then switch to external mm_ctlr, to
+--   allow external monitoring of the TSE.
+
+LIBRARY IEEE, technology_lib, common_lib, dp_lib;
+USE IEEE.std_logic_1164.ALL;
+USE technology_lib.technology_pkg.ALL;
+USE technology_lib.technology_select_pkg.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.common_mem_pkg.ALL;
+USE dp_lib.dp_stream_pkg.ALL;
+USE work.tech_tse_pkg.ALL;
+
+ENTITY tech_tse_with_setup IS
+  GENERIC (
+    g_technology   : NATURAL := c_tech_select_default;
+    g_ETH_PHY      : STRING  := "LVDS"; -- "LVDS" (default): uses LVDS IOs for ctrl_unb_common, "XCVR": uses tranceiver PHY
+    g_jumbo_en     : BOOLEAN := FALSE;
+    g_sim          : BOOLEAN := FALSE;
+    g_sim_level    : NATURAL := 0;     -- 0 = use IP model (equivalent to g_sim = FALSE); 1 = use fast serdes model;
+    g_sim_tx       : BOOLEAN := TRUE;
+    g_sim_rx       : BOOLEAN := TRUE
+  );
+  PORT (
+    -- Clocks and reset
+    mm_rst         : IN  STD_LOGIC;
+    mm_clk         : IN  STD_LOGIC;  -- MM
+    eth_clk        : IN  STD_LOGIC;  -- 125 MHz
+    tx_snk_clk     : IN  STD_LOGIC;  -- DP
+    rx_src_clk     : IN  STD_LOGIC;  -- DP
+
+    -- TSE setup
+    src_mac        : IN STD_LOGIC_VECTOR(c_48-1 DOWNTO 0);
+    setup_done     : OUT STD_LOGIC;
+
+    -- Calibration & reconfig clock
+    cal_rec_clk    : IN  STD_LOGIC := '0';
+    
+    -- Memory Mapped Peripheral
+    mm_ctlr_copi   : IN  t_mem_copi;
+    mm_ctlr_cipo   : OUT t_mem_cipo;
+
+    -- MAC transmit interface
+    -- . ST sink
+    tx_snk_in      : IN  t_dp_sosi;
+    tx_snk_out     : OUT t_dp_siso;
+
+    -- MAC receive interface
+    -- . ST Source
+    rx_src_in      : IN  t_dp_siso;
+    rx_src_out     : OUT t_dp_sosi;
+
+    -- PHY interface
+    eth_txp        : OUT STD_LOGIC;
+    eth_rxp        : IN  STD_LOGIC;
+
+    tse_led        : OUT t_tech_tse_led
+  );
+END tech_tse_with_setup;
+
+ARCHITECTURE str OF tech_tse_with_setup IS
+
+  -- Peripheral side
+  SIGNAL mm_peri_copi    : t_mem_copi;
+  SIGNAL mm_peri_cipo    : t_mem_cipo;
+
+  -- MAC specific
+  SIGNAL tx_mac_in       : t_tech_tse_tx_mac;
+  SIGNAL tx_mac_out      : t_tech_tse_tx_mac;
+  SIGNAL rx_mac_out      : t_tech_tse_rx_mac;
+
+  SIGNAL tx_sosi         : t_dp_sosi;
+
+BEGIN
+
+  -- Set up TSE as in unb_osy/unbos_eth.c
+  u_tech_tse_setup : ENTITY work.tech_tse_setup
+  GENERIC MAP (
+    g_sim      => g_sim,
+    g_jumbo_en => g_jumbo_en
+  )
+  PORT MAP (
+    -- Clocks and reset
+    mm_rst         => mm_rst,
+    mm_clk         => mm_clk,
+
+    -- TSE setup
+    src_mac        => src_mac,
+    setup_done     => setup_done,
+
+    -- Memory Mapped Peripheral
+    -- . Controller side
+    mm_ctlr_copi    => mm_ctlr_copi,
+    mm_ctlr_cipo    => mm_ctlr_cipo,
+    -- . Peripheral side
+    mm_peri_copi    => mm_peri_copi,
+    mm_peri_cipo    => mm_peri_cipo
+  );
+
+  -- Force defaults as in eth.vhd
+  tx_sosi <= func_dp_stream_error_set(tx_snk_in, 0);   -- force err field (value 0 for OK)
+
+  tx_mac_in.crc_fwd <= '0';  -- when '0' then TSE MAC generates the TX CRC field
+
+  u_tech_tse : ENTITY work.tech_tse
+  GENERIC MAP (
+    g_technology  => g_technology,
+    g_ETH_PHY     => g_ETH_PHY,
+    g_sim         => g_sim,
+    g_sim_level   => g_sim_level,
+    g_sim_tx      => g_sim_tx,
+    g_sim_rx      => g_sim_rx
+  )
+  PORT MAP (
+    -- Clocks and reset
+    mm_rst        => mm_rst,
+    mm_clk        => mm_clk,
+    eth_clk       => eth_clk,
+    tx_snk_clk    => tx_snk_clk,
+    rx_src_clk    => rx_src_clk,
+
+    -- Calibration & reconfig clock
+    cal_rec_clk   => cal_rec_clk,
+
+    -- Memory Mapped Peripheral
+    mm_sla_in     => mm_peri_copi,
+    mm_sla_out    => mm_peri_cipo,
+
+    -- MAC transmit interface
+    -- . ST sink
+    tx_snk_in     => tx_sosi,
+    tx_snk_out    => tx_snk_out,
+    -- . MAC specific
+    tx_mac_in     => tx_mac_in,
+    tx_mac_out    => tx_mac_out,
+
+    -- MAC receive interface
+    -- . ST Source
+    rx_src_in     => rx_src_in,
+    rx_src_out    => rx_src_out,
+    -- . MAC specific
+    rx_mac_out    => rx_mac_out,
+
+    -- PHY interface
+    eth_txp       => eth_txp,
+    eth_rxp       => eth_rxp,
+
+    tse_led       => tse_led
+  );
+
+END ARCHITECTURE;