]> git.the-white-hart.net Git - vhdl/commitdiff
Use SRLs for watchdog timer in PS2 controler
authorRyan <>
Thu, 18 Sep 2025 23:51:38 +0000 (18:51 -0500)
committerRyan <>
Thu, 18 Sep 2025 23:51:38 +0000 (18:51 -0500)
libraries/ps2/ps2_host_opt.vhd [new file with mode: 0644]
libraries/ps2/ps2_host_wb_opt.vhd
libraries/ps2/tests/test_ps2_host.vhd

diff --git a/libraries/ps2/ps2_host_opt.vhd b/libraries/ps2/ps2_host_opt.vhd
new file mode 100644 (file)
index 0000000..3ed255f
--- /dev/null
@@ -0,0 +1,535 @@
+--------------------------------------------------------------------------------
+-- ps2_host - Host PS2 (keyboard/mouse) interface
+--------------------------------------------------------------------------------
+-- Notes:
+--
+-- The interface to the system is Wishbone-like - ACK and DAT signals are only
+-- considered valid when the corresponding STB signal is asserted, and both may
+-- be asserted or contain data even when STB is not asserted, which must be
+-- ignored.  This applies to both tx_* and rx_* interfaces.
+--
+-- If any transfer is in progress when the system signals that it wants to
+-- transmit a byte via tx_stb_i, the controller will stall the system by not
+-- asserting tx_ack_o until both the current transfer is finished and, if the
+-- transfer is from device to the host, the system acknowledges the received
+-- byte by asserting rx_ack_i.
+--
+-- The controller will not accept new bytes to transmit to the device when
+-- inhibit is asserted, and will stall the system by not asserting tx_ack_o.
+-- If a host to device transfer is already in progress when inhibit is
+-- asserted, the transfer is completed before inhibiting the device.
+--
+-- If a device to host transfer is in progress when inhibit is asserted, the
+-- transfer will be cancelled and received bits discarded unless the transfer
+-- has reached the 11th (stop) bit.  If the transfer of the stop bit is in
+-- progress, the controller will finish receiving the byte and then inhibit the
+-- device.  The received byte will be signalled with rx_stb_o and must be
+-- acknowledged by the system with rx_ack_i.  This behavior is required by the
+-- PS2 serial protocol spec.
+--
+-- If auto_inhibit is asserted, the controller will inhibit the device from
+-- transmitting after each byte received from the device, and will uninhibit the
+-- device once the received byte is acknowledged by the system via rx_ack_i.
+-- Use of auto_inhibit is recommended unless it is known that a device will not
+-- behave predictably when inhibited.
+--
+-- Some of the error signals have imprecise timings, which is to say that it
+-- cannot strictly be determined when the error signal should be checked or
+-- possibly which transfer caused the error.  If transfer errors occur, you have
+-- bigger problems that won't be solved by knowing which transfer caused the
+-- error, so this is fine.  The variety in types of distinguishable errors is
+-- certainly overkill, as the response to any errors is generally:
+-- 1. Discard data for receive errors, retry for transmit errors
+-- 2. Reset the controller interface if (1) doesn't work
+-- 3. Give up completely if neither (1) nor (2) work
+--
+-- Error signals:
+-- tx_err_nack    - Asserted when the device fails to acknowledge a byte
+--                  transmitted from the host
+--                  Always valid, but will indicate a detected error only upon
+--                  transfer completion of each host-transmitted byte - without
+--                  "done" signalling, the timing relative to the beginning of a
+--                  transfer is imprecise
+--                  Deasserted when the interface is reset
+-- tx_err_timeout - Asserted when the device fails to transition the serial CLK
+--                  line within some time limit during host to device transfer
+--                  Always valid, but timing of error detection (and the error
+--                  itself) relative to the beginning of a transfer is imprecise
+--                  Deasserted when the interface is reset
+-- rx_err_timeout - Asserted when the device fails to transition the serial CLK
+--                  line within some time limit during device to host transfer
+--                  Always valid, but timing of error detection (and the error
+--                  itself) relative to the beginning of a transfer is imprecise,
+--                  and rx_stb_o will not be asserted after a receive timeout as
+--                  no complete transfer took place
+--                  Deasserted when the interface is reset
+-- rx_err_missed  - Asserted when the device begins another transfer to the host
+--                  before the system has acknowledged a previous transfer
+--                  Always valid, but timing of error detection (and the error
+--                  itself) is imprecise
+--                  Deasserted when the previously received byte is acknowledged
+--                  by the host via rx_ack_i
+-- rx_err_parity  - Asserted when a parity error is detected for a received byte
+--                  Valid only when rx_stb_o is asserted (may spuriously assert
+--                  while rx_stb_o is deasserted)
+--                  Recomputed with each received byte
+-- rx_err_start   - Asserted when a device to host transfer sends a one-valued
+--                  start bit
+--                  Valid only when rx_stb_o is asserted (may spuriously assert
+--                  while rx_stb_o is deasserted)
+--                  Recomputed with each received byte
+-- rx_err_stop    - Asserted when a device to host transfer sends a zero-valued
+--                  stop bit
+--                  Valid only when rx_stb_o is asserted (may spuriously assert
+--                  while rx_stb_o is deasserted)
+--                  Recomputed with each received byte
+--
+-- TODO: Accept watchdog timeout tick count as input signal from system
+-- TODO: Use separate (not watchdog timeout) tick count for transmit inhibit
+--------------------------------------------------------------------------------
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+use ieee.std_logic_misc.all;
+
+library unisim;
+use unisim.vcomponents.all;
+
+entity ps2_host_opt is
+       port (
+               -- Wishbone SYSCON
+               rst_i:          in    std_logic;
+               clk_i:          in    std_logic;
+
+               -- Transmit
+               tx_stb_i:       in    std_logic;  -- Trigger transmission of a byte
+               tx_ack_o:       out   std_logic;  -- Ready to transmit
+               tx_dat_i:       in    std_logic_vector(7 downto 0);
+
+               -- Receive
+               rx_stb_o:       out   std_logic;  -- Byte from device is ready
+               rx_ack_i:       in    std_logic;  -- Acknowledge a received byte
+               rx_dat_o:       out   std_logic_vector(7 downto 0);
+
+               -- Configuration
+               inhibit:        in    std_logic;  -- Cancel and prevent transmission from device
+               auto_inhibit:   in    std_logic;  -- Prevent transmission from device until byte is read
+
+               -- Error signals
+               tx_err_nack:    out   std_logic;  -- Transmission not acknowledged
+               tx_err_timeout: out   std_logic;  -- Device took too long to transition clock during tx
+               rx_err_timeout: out   std_logic;  -- Device took too long to transition clock during rx
+               rx_err_missed:  out   std_logic;  -- Byte from device was missed
+               rx_err_parity:  out   std_logic;  -- Parity error detected
+               rx_err_start:   out   std_logic;  -- Start bit was not 1
+               rx_err_stop:    out   std_logic;  -- Stop bit was not 1
+
+               -- Serial bus
+               ps2_clk:        inout std_logic;
+               ps2_data:       inout std_logic
+       );
+end ps2_host_opt;
+
+
+architecture behavioral of ps2_host_opt is
+
+       type state_t is (
+               S_READY,    S_INHIBIT,
+               S_RX_SHIFT, S_RX_HOLD,
+               S_TX_START, S_TX_SHIFT
+       );
+
+       signal state_reg:         state_t;
+       signal next_state:        state_t;
+
+       -- Shifter and control
+       -- start bit, 8 data bits, parity bit, stop bit all included in shift register
+       signal count_reset:       std_logic;
+       signal data_count_reg:    unsigned(3 downto 0);
+       signal count_done:        std_logic;
+       signal tx_latch_en:       std_logic;
+       signal transmit:          std_logic;
+       signal shift_en:          std_logic;
+       signal data_in_parity:    std_logic;
+       signal data_shift_reg:    std_logic_vector(10 downto 0);
+
+       -- Watchdog
+       -- SRLs divide the clock by 16, 16, and 8, so shifting 0x2710 (rounded to 0x2800) by 4+4+3=11 bits gives 0x5
+       -- This makes the watchdog less precise, but it does not need precision
+       constant TICKS_200us:     unsigned(2 downto 0) := "101";  --x"2710";  -- Assumes 50MHz clock
+       signal watchdog_x0:       std_logic;
+       signal watchdog_x1:       std_logic;
+       signal watchdog_x2:       std_logic;
+       signal watchdog_x1_ce:    std_logic;
+       signal watchdog_x2_ce:    std_logic;
+       signal watchdog_tick:     std_logic;
+       signal watchdog_kick:     std_logic;
+       signal watchdog_reg:      unsigned(2 downto 0);
+       signal watchdog_expire:   std_logic;
+
+       -- Error tracking registers
+       signal tx_nack_update:    std_logic;
+       signal tx_nack_reg:       std_logic;
+
+       signal tx_timeout_set:    std_logic;
+       signal tx_timeout_reg:    std_logic;
+
+       signal rx_parity_reg:     std_logic;
+
+       signal rx_timeout_set:    std_logic;
+       signal rx_timeout_reg:    std_logic;
+
+       signal rx_missed_set:     std_logic;
+       signal rx_missed_rst:     std_logic;
+       signal rx_missed_reg:     std_logic;
+
+       -- Serial bus signal conditioning
+       signal host_clk:          std_logic;
+       signal host_data:         std_logic;
+       signal ps2_clk_int:       std_logic;
+       signal ps2_data_int:      std_logic;
+       signal edge_detector_reg: std_logic_vector(1 downto 0);
+       signal ps2_rising_edge:   std_logic;
+       signal ps2_falling_edge:  std_logic;
+
+begin
+
+       ----------------------------------------------------------------------------
+       -- State machine
+
+       process (rst_i, clk_i, next_state)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               state_reg <= S_READY;
+                       else
+                               state_reg <= next_state;
+                       end if;
+               end if;
+       end process;
+
+       process (state_reg, ps2_rising_edge, ps2_falling_edge, watchdog_expire, tx_stb_i, rx_ack_i, inhibit, auto_inhibit, count_done, data_shift_reg)
+       begin
+               -- Default signals
+               next_state     <= state_reg;  -- Remain in current state
+               rx_stb_o       <= '0';        -- Don't present a received byte
+               tx_ack_o       <= '0';        -- Don't accept a transmit byte
+               tx_latch_en    <= '0';        -- Don't latch data from system to transmit
+               shift_en       <= '0';        -- Don't shift data through the serial bus or count bits
+               watchdog_kick  <= '0';        -- Allow watchdog to run
+               -- TODO: count_reset should default to 1 and be explicitly disabled when receiving
+               count_reset    <= '0';        -- Leave the bit counter alone
+               host_clk       <= '1';        -- Allow device to control serial clock line
+               host_data      <= '1';        -- Allow device to control serial data line
+               tx_timeout_set <= '0';        -- Don't flag TX timeout
+               rx_timeout_set <= '0';        -- Don't flag RX timeout
+               rx_missed_rst  <= '0';        -- Don't reset the RX missed flag
+               transmit       <= '0';
+
+               case state_reg is
+                       when S_READY =>
+                               -- Accept either new Tx or Rx byte
+                               tx_ack_o      <= '1';  -- Accept byte to transmit
+                               watchdog_kick <= '1';  -- Stop watchdog from running and reset
+                               count_reset   <= '1';  -- Reset bit counter
+                               if inhibit = '1' then
+                                       -- If inhibit requested, don't accept byte to transmit
+                                       tx_ack_o   <= '0';
+                                       next_state <= S_INHIBIT;
+                               elsif tx_stb_i = '1' then
+                                       -- Grab a byte from the system and start transmission
+                                       tx_latch_en <= '1';
+                                       next_state  <= S_TX_START;
+                               elsif ps2_falling_edge = '1' then
+                                       -- Begin receiving from device
+                                       count_reset     <= '0';  -- Allow the first falling edge to be counted
+                                       shift_en        <= '1';
+                                       next_state      <= S_RX_SHIFT;
+                               end if;
+
+                       when S_INHIBIT =>
+                               -- Don't accept any new Tx or Rx bytes until inhibit is lowered
+                               host_clk <= '0';
+                               if inhibit = '0' then
+                                       next_state <= S_READY;
+                               end if;
+
+                       when S_RX_SHIFT =>
+                               if inhibit = '1' and count_done = '0' then
+                                       -- Don't allow inhibit during last (stop) bit, otherwise
+                                       -- cancel and discard reception
+                                       next_state <= S_INHIBIT;
+                               elsif ps2_falling_edge = '1' then
+                                       -- Sample data on falling edge and kick the watchdog
+                                       watchdog_kick    <= '1';
+                                       shift_en         <= '1';
+                               --elsif ps2_rising_edge = '1' and count_done = '1' then
+                               elsif count_done = '1' then
+                                       -- Done on XrisingXedgeX of last bit
+                                       -- Don't wait for the rising edge so we can keep the clock
+                                       -- low when auto-inhibiting - this prevents us from dropping
+                                       -- the clock due to auto-inhibit and picking up our own
+                                       -- falling edge as the beginning of a new byte, causing
+                                       -- spurrious rx timeout errors
+                                       next_state <= S_RX_HOLD;
+                               elsif watchdog_expire = '1' then
+                                       -- If device stops responding, abort and return to ready
+                                       rx_timeout_set <= '1';
+                                       next_state <= S_READY;
+                               end if;
+
+                       when S_RX_HOLD =>
+                               -- Report reception to system and don't accept bytes to transmit
+                               -- until the shift register is made available by acknowledgement
+                               rx_stb_o <= '1';
+                               count_reset <= '1';  -- This prevents underflow when auto-inhibiting for a single clock cycle
+                               if auto_inhibit = '1' or inhibit = '1' then
+                                       -- If inhibit was asserted during the stop bit, the byte is
+                                       -- received, and we inhibit now - or if auto-inhibition is
+                                       -- requested after reception to avoid missing data
+                                       host_clk <= '0';
+                               end if;
+                               if rx_ack_i = '1' then
+                                       -- Upon acknowledgement, either return to ready or handle
+                                       -- inhibition that was deferred due to assertion during the
+                                       -- stop bit
+                                       rx_missed_rst <= '1';
+                                       if inhibit = '1' then
+                                               next_state <= S_INHIBIT;
+                                       else
+                                               -- We may reenter the ready state while the device is
+                                               -- still holding the clock low, since we don't wait for
+                                               -- the rising edge to enter rx_hold (to support auto-
+                                               -- inhibit)
+                                               -- This will not cause problems, as transmitting a new
+                                               -- byte begins with inhibiting the deivce for a time
+                                               -- anyway, and the device knows what it's doing when it
+                                               -- wants to send the next byte
+                                               next_state <= S_READY;
+                                       end if;
+                               end if;
+
+                       when S_TX_START =>
+                               -- Inhibit device and transmit the start bit
+                               transmit <= '1';
+                               host_clk      <= '0';
+                               host_data     <= data_shift_reg(0);
+                               if watchdog_expire = '1' then
+                                       -- Use the watchdog as a timer to inhibit the device for some time
+                                       watchdog_kick <= '1';
+                                       next_state    <= S_TX_SHIFT;
+                               end if;
+
+                       when S_TX_SHIFT =>
+                               transmit <= '1';
+                               host_data <= data_shift_reg(0);  -- Transmit data bit (will still be start bit until first falling edge)
+                               if ps2_falling_edge = '1' then
+                                       -- Change data on falling edge and kick the watchdog
+                                       -- The shift register also shifts data back in, which will catch the device ACK
+                                       watchdog_kick <= '1';
+                                       shift_en      <= '1';
+                                       if count_done = '1' then
+                                               tx_nack_update <= '1';
+                                       end if;
+                               elsif ps2_rising_edge = '1' and count_done = '1' then
+                                       -- Done on rising edge of last bit
+                                       next_state <= S_READY;
+                               elsif watchdog_expire = '1' then
+                                       -- If device stops responding, abort and return to ready
+                                       tx_timeout_set <= '1';
+                                       next_state <= S_READY;
+                               end if;
+
+                       when others =>
+                               next_state <= S_READY;
+               end case;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Error tracking registers
+
+       process (rst_i, clk_i, tx_nack_update, ps2_data_int)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               tx_nack_reg <= '0';
+                       elsif tx_nack_update = '1' then
+                               tx_nack_reg <= ps2_data_int;
+                       end if;
+               end if;
+       end process;
+       tx_err_nack <= tx_nack_reg;
+
+       process (rst_i, clk_i, tx_timeout_set)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               tx_timeout_reg <= '0';
+                       elsif tx_timeout_set = '1' then
+                               tx_timeout_reg <= '1';
+                       end if;
+               end if;
+       end process;
+       tx_err_timeout <= tx_timeout_reg;
+
+       process (rst_i, clk_i, count_reset, shift_en, rx_parity_reg, ps2_data_int)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' or count_reset = '1' then
+                               rx_parity_reg <= '0';
+                       elsif shift_en = '1' then
+                               rx_parity_reg <= rx_parity_reg xor ps2_data_int;
+                       end if;
+               end if;
+       end process;
+       rx_err_parity <= rx_parity_reg;
+       rx_err_start  <= data_shift_reg(0);
+       rx_dat_o      <= data_shift_reg(8 downto 1);
+       rx_err_stop   <= not data_shift_reg(10);
+
+       process (rst_i, clk_i, rx_timeout_set)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               rx_timeout_reg <= '0';
+                       elsif rx_timeout_set = '1' then
+                               rx_timeout_reg <= '1';
+                       end if;
+               end if;
+       end process;
+       rx_err_timeout <= rx_timeout_reg;
+
+       process (rst_i, clk_i, rx_missed_set)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' or rx_missed_rst = '1' then
+                               rx_missed_reg <= '0';
+                       elsif rx_missed_set = '1' then
+                               rx_missed_reg <= '1';
+                       end if;
+               end if;
+       end process;
+       rx_err_missed <= rx_missed_reg;
+
+
+       ----------------------------------------------------------------------------
+       -- Data shift register and bit counter
+
+       -- Count down to zero and halt
+       process (rst_i, clk_i, count_reset, shift_en, data_count_reg)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' or count_reset = '1' then
+                               data_count_reg <= x"b";
+                       elsif shift_en = '1' then
+                               data_count_reg <= data_count_reg - 1;
+                       end if;
+               end if;
+       end process;
+       count_done <= not or_reduce(std_logic_vector(data_count_reg));
+
+       -- Transmit data latched when tx_latch_en is active
+       -- LSBs shifted out and PS2 data shifted into the MSB when shift_en is active
+       -- Used for both Tx and Rx
+       process (clk_i, tx_latch_en, shift_en, data_in_parity, tx_dat_i, ps2_data_int, data_shift_reg, transmit)
+       begin
+               if rising_edge(clk_i) then
+                       if tx_latch_en = '1' then
+                               data_shift_reg <= '1' & data_in_parity & tx_dat_i & '0';
+                       elsif shift_en = '1' then
+                               -- The "or transmit" signal forces ones to be shifted in while
+                               -- transmitting, which prevents from sampling our own start bit
+                               -- and shifting it out during the acknowledge period, which
+                               -- would acknowledge our own transmission
+                               data_shift_reg <= (ps2_data_int or transmit) & data_shift_reg(data_shift_reg'high downto 1);
+                       end if;
+               end if;
+       end process;
+       data_in_parity <= not xor_reduce(tx_dat_i);
+
+
+       ----------------------------------------------------------------------------
+       -- Watchdog timer, reset to 200us when kicked, stop at zero
+
+       e_wc_clk_0: srl16
+               generic map (INIT => x"0001")
+               port map (
+                       clk => clk_i,
+                       a0  => '1',
+                       a1  => '1',
+                       a2  => '1',
+                       a3  => '1',
+                       d   => watchdog_x0,
+                       q   => watchdog_x0
+               );
+
+       watchdog_x1_ce <= watchdog_x0;
+       e_wc_clk_1: srl16e
+               generic map (INIT => x"0001")
+               port map (
+                       clk => clk_i,
+                       ce  => watchdog_x1_ce,
+                       a0  => '1',
+                       a1  => '1',
+                       a2  => '1',
+                       a3  => '1',
+                       d   => watchdog_x1,
+                       q   => watchdog_x1
+               );
+
+       watchdog_x2_ce <= watchdog_x1 and watchdog_x0;
+       e_wc_clk_2: srl16e
+               generic map (INIT => x"0001")
+               port map (
+                       clk => clk_i,
+                       ce  => watchdog_x2_ce,
+                       a0  => '1',
+                       a1  => '1',
+                       a2  => '1',
+                       a3  => '0',
+                       d   => watchdog_x2,
+                       q   => watchdog_x2
+               );
+       watchdog_tick <= watchdog_x2 and watchdog_x1 and watchdog_x0;
+
+       process (rst_i, clk_i, watchdog_kick, watchdog_expire, watchdog_reg, watchdog_tick)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' or watchdog_kick = '1' then
+                               watchdog_reg <= TICKS_200us;
+                       elsif watchdog_expire = '0' and watchdog_tick = '1' then
+                               watchdog_reg <= watchdog_reg - 1;
+                       end if;
+               end if;
+       end process;
+       watchdog_expire <= not or_reduce(std_logic_vector(watchdog_reg));
+
+
+       ----------------------------------------------------------------------------
+       -- PS2 signal conditioning
+
+       -- Strengthen input signals ('Z','H' -> '1') for simulation
+       ps2_clk_int  <= '0' when ps2_clk  = '0' else '1';
+       ps2_data_int <= '0' when ps2_data = '0' else '1';
+
+       -- Detect rising and falling edges
+       process (rst_i, clk_i, edge_detector_reg, ps2_clk_int)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               edge_detector_reg <= (others => '1');
+                       else
+                               edge_detector_reg <= edge_detector_reg(edge_detector_reg'high-1 downto 0) & ps2_clk_int;
+                       end if;
+               end if;
+       end process;
+       ps2_falling_edge <= '1' when edge_detector_reg = "10" else '0';
+       ps2_rising_edge  <= '1' when edge_detector_reg = "01" else '0';
+
+       -- Weaken output signals to allow device to pull low
+       ps2_clk  <= '0' when host_clk  = '0' else 'Z';
+       ps2_data <= '0' when host_data = '0' else 'Z';
+
+end behavioral;
index 2a824d93f1295e85fbc9b603a01e430eaa351ace..b1ab7b3e1553ef7bb23130f35cdf6f8b003916aa 100644 (file)
@@ -286,7 +286,7 @@ begin
                        is_full  => rxq_full
                );
 
-       e_ps2: entity work.ps2_host
+       e_ps2: entity work.ps2_host_opt
                port map (
                        rst_i          => iface_rst,
                        clk_i          => clk_i,
index 2403bc0d815bababe0e1867ea02dd4f5839e4a7e..afad2b6472a49554f58f08d61f8d634a24ff37a1 100644 (file)
@@ -175,7 +175,7 @@ begin
        end process;
 
 
-       uut: entity work.ps2_host
+       uut: entity work.ps2_host_opt
                port map (
                        rst_i          => rst_i,
                        clk_i          => clk_i,