~ruther/vhdl-spi-2

dc0e370ab44f26ba06f5e709c826cb73b3c15fd8 — Rutherther 3 months ago ff6a0bd
feat: implement initial hdl_spi
A hdl_spi/.envrc => hdl_spi/.envrc +1 -0
@@ 0,0 1,1 @@
use guix

A hdl_spi/.gitignore => hdl_spi/.gitignore +7 -0
@@ 0,0 1,7 @@
modelsim.ini
sim_build/
__pycache__/
transcript
vsim.wlf
vsim_stacktrace.vstf
core
\ No newline at end of file

A hdl_spi/.project => hdl_spi/.project +0 -0
A hdl_spi/manifest.scm => hdl_spi/manifest.scm +61 -0
@@ 0,0 1,61 @@
(use-modules
 ((guix licenses) #:prefix license:)
 (guix packages)
 (guix download)
 (gnu packages python-build)
 (guix build-system python)
 (guix build-system pyproject))

(define-public python-find-libpython
  (package
    (name "python-find-libpython")
    (version "0.4.0")
    (source
     (origin
       (method url-fetch)
       (uri (pypi-uri "find_libpython" version))
       (sha256
        (base32 "1rh3dj81qwl1v7ckni12abgw2hbag79xx4km5lxmdnvx776wvya6"))))
    (build-system pyproject-build-system)
    (native-inputs (list python-setuptools python-wheel))
    (home-page "https://github.com/ktbarrett/find_libpython")
    (synopsis
     "Finds the libpython associated with your environment, wherever it may be hiding")
    (description
     "Finds the libpython associated with your environment, wherever it may be hiding.")
    (license license:expat)))

(define-public python-cocotb
  (package
    (name "python-cocotb")
    (version "1.9.2")
    (source
     (origin
       (method url-fetch)
       (uri (pypi-uri "cocotb" version))
       (sha256
        (base32 "0lhnvfzzfkz41pchf0sg302ssj0bvipcafh861a4xcf13vsymkg4"))))
    (build-system pyproject-build-system)
    (propagated-inputs (list python-find-libpython))
    (native-inputs (list python-setuptools python-wheel))
    (arguments
     `(#:tests? #f))
    (home-page "https://www.cocotb.org")
    (synopsis
     "cocotb is a coroutine based cosimulation library for writing VHDL and Verilog testbenches in Python.")
    (description
     "cocotb is a coroutine based cosimulation library for writing VHDL and Verilog
testbenches in Python.")
    (license license:bsd-3)))

(concatenate-manifests
 (list
  (packages->manifest
   (list python-cocotb))

  (specifications->manifest
   (list
    "python-pytest"
    "python"
    "vhdl-ls"
    "make"))))

A hdl_spi/src/README => hdl_spi/src/README +57 -0
@@ 0,0 1,57 @@
spi_master
  SIZES (8, 16 default)
  SIZES_LOG2 1

  DIVISORS_LOG2 3
  DIVISORS (2, 4, 8, 16, 32, 64, 128, 256)

  CSN_PULSE_CYCLES (1 - divided clock cycle)

  INOUTS
    sck, miso, mosi

  STATE
    busy
    err_lost_rx_data
    clear_err_lost_rx_data

  DATA
    tx_en ( enable transmission. If disabled, mosi will be 'z', so miso and mosi can be connected )
    tx_valid ( the data on tx_data are valid )
    tx_ready ( ready to receive data. Receiving as soon as tx_valid is 1, the next edge will not be ready anymore)
    tx_data ( the data to transmit )

    rx_en ( reception can be disabled when you want to ignore the data )
    rx_valid ( the data on rx_data are valid )
    rx_confirm ( taking data from rx_data )
    rx_data ( the data to receive. If data aren't received during next word, the communication is stalled! )
    rx_block_on_full ( should rx block communication on full? if not, data can be lost if they are not read in time )

  CONFIGURATION
    en

    clock_polarity
    clock_phase

    size_sel
    div_sel

    pulse_csn

  STRUCTURE
    tx: piso_register
    rx: sipo_register
    ctrl: spi_master_ctrl
    clk_gen: spi_clkgen

spi_slave
  tx: piso_register
  rx: sipo_register
  ctrl: spi_slave_ctrl

spi_dual
  tx: piso_register
  rx: sipo_register
  master_ctrl: spi_master_ctrl
  slave_ctrl: spi_slave_ctrl
  clk_gen: spi_clkgen
\ No newline at end of file

A hdl_spi/src/register.vhd => hdl_spi/src/register.vhd +34 -0
@@ 0,0 1,34 @@
library ieee;
use ieee.std_logic_1164.all;


entity reg is

  generic (
    SIZE : natural := 1);

  port (
    clk_i   : in  std_logic;
    rst_in  : in  std_logic;
    d_i     : in  std_logic_vector(SIZE - 1 downto 0);
    q_o     : out std_logic_vector(SIZE - 1 downto 0);
    latch_i : in  std_logic);

end entity reg;

architecture a1 of reg is

begin  -- architecture a1

  set_q: process (clk_i) is
  begin  -- process set_q
    if rising_edge(clk_i) then          -- rising clock edge
      if rst_in = '0' then              -- synchronous reset (active low)
        q_o <= (others => '0');
      elsif latch_i = '1' then
        q_o <= d_i;
      end if;
    end if;
  end process set_q;

end architecture a1;

A hdl_spi/src/rs_latch.vhd => hdl_spi/src/rs_latch.vhd +26 -0
@@ 0,0 1,26 @@
library ieee;
use ieee.std_logic_1164.all;

entity rs_latch is

  port (
    reset_i : in  std_logic;
    set_i   : in  std_logic;
    q_o     : out std_logic);

end entity rs_latch;

architecture a1 of rs_latch is

begin  -- architecture a1

  data: process (reset_i, set_i) is
  begin  -- process data
    if set_i = '1' then
      q_o <= '1';
    elsif reset_i = '1' then
      q_o <= '0';
    end if;
  end process data;

end architecture a1;

A hdl_spi/src/shift_register.vhd => hdl_spi/src/shift_register.vhd +44 -0
@@ 0,0 1,44 @@
library ieee;
use ieee.std_logic_1164.all;

entity shift_register is

  generic (
    SIZE : natural);

  port (
    clk_i   : in  std_logic;
    rst_in  : in  std_logic;
    shift_i : in  std_logic;
    sd_i    : in  std_logic;
    sd_o    : out std_logic;
    latch_i : in  std_logic;
    data_i  : in  std_logic_vector(SIZE - 1 downto 0);
    data_o  : out std_logic_vector(SIZE - 1 downto 0));

end entity shift_register;

architecture a1 of shift_register is
  signal next_register : std_logic_vector(SIZE - 1 downto 0);
  signal curr_register : std_logic_vector(SIZE - 1 downto 0);
begin  -- architecture a1

  set_data: process (clk_i) is
  begin  -- process set_data
    if rising_edge(clk_i) then          -- rising clock edge
      if rst_in = '0' then              -- synchronous reset (active low)
        curr_register <= (others => '0');
      else
        curr_register <= next_register;
      end if;
    end if;
  end process set_data;

  next_register <= data_i when latch_i = '1' else
                   curr_register(SIZE - 2 downto 0) & sd_i when shift_i = '1' else
                   curr_register;

  sd_o <= curr_register(SIZE - 1);
  data_o <= curr_register;

end architecture a1;

A hdl_spi/src/spi_clkgen.vhd => hdl_spi/src/spi_clkgen.vhd +95 -0
@@ 0,0 1,95 @@
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
use work.spi_pkg.all;

entity spi_clkgen is

  generic (
    DIVISORS         : natural_vector := (2, 4, 6, 8, 16, 32, 64, 128, 256);
    DIVISORS_LOG2    : natural := 3
  );

  port (
    clk_i            : in  std_logic;
    rst_in           : in  std_logic;
    start_i          : in  std_logic;
    div_sel_i        : in  std_logic_vector(DIVISORS_LOG2 - 1 downto 0);
    clock_polarity_i : in  std_logic;
    clock_phase_i    : in  std_logic;
    sck_o            : out std_logic;
    sck_mask_i       : in  std_logic;
    clock_rising_o   : out std_logic;
    sample_data_o    : out std_logic;
    change_data_o    : out std_logic);

end entity spi_clkgen;

architecture a1 of spi_clkgen is
  constant MAX : natural := get_max_natural(DIVISORS);

  signal curr_running : std_logic;
  signal next_running : std_logic;

  signal selected_divisor : natural range 0 to MAX - 1 := 1;
  signal changing : std_logic;

  signal curr_counter : integer range 0 to MAX - 1;
  signal next_counter : integer range 0 to MAX - 1;

  signal curr_sck : std_logic;
  signal next_sck : std_logic;

  signal next_sample_data : std_logic;
  signal curr_sample_data : std_logic;

  signal next_change_data : std_logic;
  signal curr_change_data : std_logic;
begin  -- architecture a1

  set_data: process (clk_i) is
  begin  -- process set_data
    if rising_edge(clk_i) then          -- rising clock edge
      if rst_in = '0' then              -- synchronous reset (active low)
        curr_running <= '0';
        curr_sck <= '0';
        curr_counter <= 0;
        curr_sample_data <= '0';
        curr_change_data <= '0';
      else
        curr_running <= next_running;
        curr_sck <= next_sck;
        curr_counter <= next_counter;
        curr_sample_data <= next_sample_data;
        curr_change_data <= next_change_data;
      end if;
    end if;
  end process set_data;

  selected_divisor <= DIVISORS(to_integer(unsigned(div_sel_i)));

  changing <= '1' when curr_counter = 0 and curr_running = '1' else '0';

  next_counter <= selected_divisor - 1 when changing = '1' else
                  0 when curr_counter = 0 else
                  curr_counter - 1 when curr_running = '1' else
                  selected_divisor - 1;

  next_sample_data <= '1' when curr_sck = clock_phase_i and changing = '1' else '0';
  next_change_data <= '1' when curr_sck /= clock_phase_i and changing = '1' else '0';

  next_sck <= not curr_sck when changing = '1'
              else curr_sck when curr_running = '1' else
              clock_polarity_i;

  next_running <= start_i;

  sck_o <= clock_polarity_i when sck_mask_i = '0' else
           curr_sck when clock_polarity_i = '0' else
           not curr_sck;

  clock_rising_o <= curr_sample_data;
  sample_data_o <= curr_sample_data and sck_mask_i;
  change_data_o <= curr_change_data and sck_mask_i;

end architecture a1;

A hdl_spi/src/spi_master.vhd => hdl_spi/src/spi_master.vhd +165 -0
@@ 0,0 1,165 @@
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;

use work.spi_pkg.all;

entity spi_master is

  generic (
    SIZES            : natural_vector := (8, 16);
    SIZES_2LOG       : natural := 1;
    DIVISORS         : natural_vector := (2, 4, 6, 8, 16, 32, 64, 128, 256);
    DIVISORS_LOG2    : natural := 3;
    CSN_PULSE_CYCLES : natural := 1
  );

  port (
    -- IOs
    sck_o                : out std_logic;
    miso_i               : in  std_logic;
    mosi_o               : out std_logic;
    csn_o                : out std_logic;
    -- Control
    clk_i                : in  std_logic;
    rst_in               : in  std_logic;
    en_i                 : in  std_logic;
    clock_polarity_i     : in  std_logic;
    clock_phase_i        : in  std_logic;
    size_sel_i           : in  std_logic_vector(SIZES_2LOG - 1 downto 0);
    div_sel_i            : in  std_logic_vector(DIVISORS_LOG2 - 1 downto 0);
    pulse_csn_i          : in  std_logic;
    rx_block_on_full_i   : in  std_logic;
    -- Data
    -- Rx
    rx_en_i              : in  std_logic;
    rx_data_o            : out std_logic_vector(get_max_natural(SIZES) - 1 downto 0);
    rx_valid_o           : out std_logic;
    rx_ready_i           : out std_logic;
    -- Tx
    tx_en_i              : in  std_logic;
    tx_data_i            : in  std_logic_vector(get_max_natural(SIZES) - 1 downto 0);
    tx_valid_i           : out std_logic;
    tx_ready_o           : out std_logic;
    -- State
    busy_o               : out std_logic;
    err_lost_rx_data_o   : out std_logic;
    clear_lost_rx_data_i : in  std_logic);

end entity spi_master;

architecture a1 of spi_master is
  constant MAX_SIZE : natural := get_max_natural(SIZES);

  signal rst_n : std_logic;

  signal ctrl_rst : std_logic;

  signal latch_sample_data     : std_logic;
  signal clock_rising          : std_logic;
  signal latch_change_data_out : std_logic;
  signal latch_new_tx_data     : std_logic;

  signal tx_serial_data : std_logic;

  signal sck : std_logic;
  signal csn : std_logic;
  signal mosi : std_logic_vector(0 downto 0);

  signal start_clock : std_logic;

  signal sck_mask : std_logic;
  signal sck_en : std_logic;
  signal csn_en : std_logic;
  signal mosi_en : std_logic;
  signal miso_en : std_logic;

  signal selected_size : natural;

begin  -- architecture a1
  rst_n <= rst_in and ctrl_rst;
  selected_size <= SIZES(to_integer(unsigned(size_sel_i)));

  ctrl : entity work.spi_master_ctrl
    generic map (
      SIZES            => SIZES,
      SIZES_2LOG       => SIZES_2LOG,
      CSN_PULSE_CYCLES => CSN_PULSE_CYCLES)
    port map (
      clk_i                => clk_i,
      rst_in               => rst_in,
      en_i                 => en_i,
      size_sel_i           => size_sel_i,
      pulse_csn_i          => pulse_csn_i,
      clock_rising_i       => clock_rising,
      rx_block_on_full_i   => rx_block_on_full_i,
      rx_en_i              => rx_en_i,
      rx_ready_i           => rx_ready_i,
      rx_valid_o           => rx_valid_o,
      tx_en_i              => tx_en_i,
      tx_valid_i           => tx_valid_i,
      tx_ready_o           => tx_ready_o,
      busy_o               => busy_o,
      err_lost_rx_data_o   => err_lost_rx_data_o,
      clear_lost_rx_data_i => clear_lost_rx_data_i,
      rst_on               => ctrl_rst,
      csn_o                => csn,
      csn_en_o             => csn_en,
      mosi_en_o            => mosi_en,
      miso_en_o            => miso_en,
      sck_mask_o           => sck_mask,
      sck_en_o             => sck_en,
      gen_clk_en_o         => start_clock,
      latch_tx_data_o      => latch_new_tx_data);

  clkgen : entity work.spi_clkgen
    generic map (
      DIVISORS      => DIVISORS,
      DIVISORS_LOG2 => DIVISORS_LOG2)
    port map (
      clk_i            => clk_i,
      rst_in           => rst_n,
      start_i          => start_clock,
      div_sel_i        => div_sel_i,
      clock_polarity_i => clock_polarity_i,
      clock_phase_i    => clock_phase_i,
      sck_o            => sck,
      sck_mask_i       => sck_mask,
      clock_rising_o   => clock_rising,
      sample_data_o    => latch_sample_data,
      change_data_o    => latch_change_data_out);

  shift_register: entity work.shift_register
    generic map (
      SIZE => MAX_SIZE)
    port map (
      clk_i => clk_i,
      rst_in => rst_in,
      -- Control
      shift_i => latch_sample_data,     -- sampling
      latch_i => latch_new_tx_data,     -- latching tx data
      -- Parallel
      data_i => tx_data_i,
      data_o => rx_data_o,
      -- Serial
      sd_i => miso_i,
      sd_o => open);

  tx_serial_data <= rx_data_o(selected_size - 1);

  mosi_reg : entity work.reg
    generic map (
      SIZE => 1)
    port map (
      -- outputting different bit on mosi
      clk_i   => clk_i,
      rst_in  => rst_n,
      d_i     => (0 => tx_serial_data),
      q_o     => mosi,
      latch_i => latch_change_data_out);

  sck_o <= sck when sck_en = '1' else 'Z';
  mosi_o <= mosi(0) when mosi_en = '1' else 'Z';
  csn_o <= csn when csn_en = '1' else 'Z';

end architecture a1;

A hdl_spi/src/spi_master_ctrl.vhd => hdl_spi/src/spi_master_ctrl.vhd +270 -0
@@ 0,0 1,270 @@
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
use work.spi_pkg.all;

entity spi_master_ctrl is

  generic (
    SIZES            : natural_vector := (8, 16);
    SIZES_2LOG       : natural := 1;
    CSN_PULSE_CYCLES : natural := 1
  );

  port (
    clk_i                : in  std_logic;
    rst_in               : in  std_logic;
    en_i                 : in  std_logic;
    size_sel_i           : in  std_logic_vector(SIZES_2LOG - 1 downto 0);
    pulse_csn_i          : in  std_logic;
    clock_rising_i       : in  std_logic;
    rx_block_on_full_i   : in  std_logic;
    rx_en_i              : in  std_logic;
    rx_valid_o           : out std_logic;
    rx_ready_i           : in  std_logic;
    tx_en_i              : in  std_logic;
    tx_valid_i           : in  std_logic;
    tx_ready_o           : out std_logic;
    busy_o               : out std_logic;
    err_lost_rx_data_o   : out std_logic;
    clear_lost_rx_data_i : in  std_logic;
    rst_on               : out std_logic;
    csn_o                : out std_logic;
    csn_en_o             : out std_logic;
    mosi_en_o            : out std_logic;
    miso_en_o            : out std_logic;
    sck_mask_o           : out std_logic;
    sck_en_o             : out std_logic;
    gen_clk_en_o         : out std_logic;
    latch_tx_data_o      : out std_logic
  );

end entity spi_master_ctrl;

architecture a1 of spi_master_ctrl is
  constant MAX_SIZE : natural := get_max_natural(SIZES);

  type states_t is (RESET, IDLE, SHIFTING, NEXT_DATA, CSN_PULSE, CSN_RISING);

  type tx_states_t is (IDLE, TX_LATCHING_DATA, TX_LATCHED, TX_WAITING);
  type rx_states_t is (IDLE, RX_GOT_DATA, RX_INVALID_DATA);

  signal rx_block : std_logic;

  signal curr_rx_state : rx_states_t;
  signal next_rx_state : rx_states_t;

  signal curr_tx_state : tx_states_t;
  signal next_tx_state : tx_states_t;

  signal curr_state : states_t;
  signal next_state : states_t;

  signal curr_counter : natural;
  signal next_counter : natural;
  signal zero : std_logic;

  signal set_lost_rx_data : std_logic;

  signal tx_got_data : std_logic;
  signal ack_tx_got_data : std_logic;

  signal transmission_done : std_logic;

  signal shifting_length : integer range 0 to MAX_SIZE;
begin  -- architecture a1
  registers: process (clk_i) is
  begin  -- process registers
    if rising_edge(clk_i) then          -- rising clock edge
      if rst_in = '0' then              -- synchronous reset (active low)
        curr_counter <= 0;
        curr_state <= RESET;
        curr_tx_state <= IDLE;
        curr_rx_state <= IDLE;
      else
        curr_counter <= next_counter;
        curr_state <= next_state;
        curr_tx_state <= next_tx_state;
        curr_rx_state <= next_rx_state;
      end if;
    end if;
  end process registers;

  state: process (all) is
    procedure switch_to (
      constant state   : in states_t;
      constant counter : in natural) is
    begin  -- procedure switch_to
      next_state <= state;
      next_counter <= counter;
    end procedure switch_to;
  begin  -- process state_sel
    next_counter <= curr_counter;
    if curr_counter /= 0 and clock_rising_i = '1' then
      next_counter <= curr_counter - 1;
    end if;

    transmission_done <= '0';
    next_state <= curr_state;

    gen_clk_en_o <= '1';
    ack_tx_got_data <= '0';

    rst_on <= '1';

    sck_mask_o <= '0';
    busy_o <= '1';
    csn_o <= '1';

    case curr_state is
      when RESET =>
        switch_to(IDLE, 0);
        next_state <= IDLE;
        rst_on <= '0';
        gen_clk_en_o <= '0';
        csn_o <= '1';
      when IDLE =>
        busy_o <= '0';
        gen_clk_en_o <= '0';

        if tx_got_data = '1' then
          switch_to(SHIFTING, shifting_length);
          ack_tx_got_data <= '1';
        end if;
      when SHIFTING =>
        csn_o <= '0';
        sck_mask_o <= '1';

        if zero = '1' then
          sck_mask_o <= '1';
          transmission_done <= '1';
          if pulse_csn_i = '1' then
            switch_to(CSN_PULSE, CSN_PULSE_CYCLES);
          else
            switch_to(NEXT_DATA, 0);
          end if;
        end if;
      when NEXT_DATA =>
        next_state <= CSN_RISING;
        csn_o <= '0';

        if zero = '1' then
          if tx_got_data = '1' then
            if curr_counter = 0 then
              switch_to(SHIFTING, shifting_length);
              ack_tx_got_data <= '1';
            end if;
          else
            csn_o <= '1';
            switch_to(IDLE, 0);
          end if;
        end if;

      when CSN_PULSE =>
        csn_o <= '1';

        if zero = '1' then
          switch_to(NEXT_DATA, 1);
        end if;
      when others =>
        next_state <= RESET;
    end case;
  end process state;

  tx_state: process(all) is
  begin  -- process tx_state
    next_tx_state <= curr_tx_state;

    latch_tx_data_o <= '0';
    tx_got_data <= '0';

    case curr_tx_state is
      when IDLE =>
        next_tx_state <= TX_LATCHING_DATA;
      when TX_LATCHING_DATA =>
        tx_ready_o <= '1';

        if tx_valid_i = '1' then
          tx_got_data <= '1';
          latch_tx_data_o <= '1';
          next_tx_state <= TX_LATCHED;

          if ack_tx_got_data = '1' then
            next_tx_state <= TX_WAITING;
          end if;
        end if;
      when TX_LATCHED =>
        tx_got_data <= '1';

        if ack_tx_got_data = '1' then
          next_tx_state <= TX_WAITING;
        end if;
      when TX_WAITING =>
        if transmission_done = '1' and rx_block = '0' then
          next_tx_state <= TX_LATCHING_DATA;
        end if;
      when others =>
        next_tx_state <= IDLE;
    end case;

    if curr_state = RESET then
      next_tx_state <= IDLE;
    end if;
  end process tx_state;

  rx_state: process(all) is
  begin  -- process rx_state
    next_rx_state <= curr_rx_state;

    rx_block <= rx_block_on_full_i;
    rx_valid_o <= '0';
    set_lost_rx_data <= '0';

    case curr_rx_state is
      when IDLE =>
        next_rx_state <= RX_INVALID_DATA;
      when RX_GOT_DATA =>
        rx_valid_o <= '1';
        if rx_ready_i = '1' or tx_got_data = '1' then
          next_rx_state <= RX_INVALID_DATA;
          rx_block <= '0';
          rx_valid_o <= '0';

          if rx_ready_i = '0' then
            set_lost_rx_data <= '1';
          end if;
        end if;
      when RX_INVALID_DATA =>
        rx_block <= '0';
        if transmission_done = '1' then
          rx_block <= rx_block_on_full_i;
          next_rx_state <= RX_GOT_DATA;
          rx_valid_o <= '1';            -- TODO check
        end if;
      when others =>
        next_rx_state <= IDLE;
    end case;

    if curr_state = RESET then
      next_rx_state <= IDLE;
    end if;
  end process rx_state;

  error_rx_lost : entity work.rs_latch
    port map (
      set_i   => set_lost_rx_data,
      reset_i => clear_lost_rx_data_i,
      q_o     => err_lost_rx_data_o);

  -- Internal
  shifting_length <= SIZES(to_integer(unsigned(size_sel_i)));
  zero <= '1' when curr_counter = 0 else '0';

  -- Enable IOs
  miso_en_o <= en_i and rx_en_i;
  sck_en_o <= en_i;
  mosi_en_o <= en_i and tx_en_i;
  csn_en_o <= en_i;
  sck_en_o <= en_i;                      -- TODO make it configurable so sck can be Z when not commnicating

end architecture a1;

A hdl_spi/src/spi_pkg.vhd => hdl_spi/src/spi_pkg.vhd +30 -0
@@ 0,0 1,30 @@
library ieee;
use ieee.std_logic_1164.all;

package spi_pkg is

  type natural_vector is array (natural range <>) of natural;

  function get_max_natural (
    constant divisors : natural_vector)
    return natural;

end package spi_pkg;

package body spi_pkg is

  function get_max_natural (
    constant divisors : natural_vector)
    return natural is
    variable max : natural := divisors(divisors'left);
  begin
    for i in divisors'range loop
      if divisors(i) > max then
        max := divisors(i);
      end if;
    end loop;  -- i

    return max;
  end function;

end package body spi_pkg;

A hdl_spi/tests/Makefile => hdl_spi/tests/Makefile +20 -0
@@ 0,0 1,20 @@
# Makefile

# defaults
SIM ?= questa
TOPLEVEL_LANG ?= vhdl

SRC = $(PWD)/../src

VHDL_SOURCES=$(SRC)/spi_pkg.vhd $(wildcard $(SRC)/*.vhd)

VCOM_ARGS = -2008

# TOPLEVEL is the name of the toplevel module in your Verilog or VHDL file
TOPLEVEL = spi_master

# MODULE is the basename of the Python test file
MODULE = test

# include cocotb's make rules to take care of the simulator setup
include $(shell cocotb-config --makefiles)/Makefile.sim

A hdl_spi/tests/results.xml => hdl_spi/tests/results.xml +6 -0
@@ 0,0 1,6 @@
<testsuites name="results">
  <testsuite name="all" package="all">
    <property name="random_seed" value="1735055524" />
    <testcase name="simple_test" classname="test" file="/home/ruther/doc/uni/master-2/first_semester/mam/sem/hdl_spi/tests/test.py" lineno="4" time="1.6984877586364746" sim_time_ns="1025.001" ratio_time="603.4785913457854" />
  </testsuite>
</testsuites>

A hdl_spi/tests/test.py => hdl_spi/tests/test.py +48 -0
@@ 0,0 1,48 @@
import cocotb
from cocotb.triggers import Timer

@cocotb.test()
async def simple_test(dut):
    dut.miso_i.value = 1;
    dut.clk_i.value = 0;
    dut.rst_in.value = 0;
    dut.en_i.value = 1;
    dut.clock_polarity_i.value = 0;
    dut.clock_phase_i.value = 0;
    dut.size_sel_i.value = 0;
    dut.div_sel_i.value = 0;
    dut.pulse_csn_i.value = 0;
    dut.rx_block_on_full_i.value = 0;
    dut.rx_en_i.value = 1;
    dut.rx_ready_i.value = 0;
    dut.tx_en_i.value = 1;
    dut.tx_valid_i.value = 0;
    dut.clear_lost_rx_data_i.value = 1;

    await Timer(5, "ns")
    dut.rst_in.value = 1;

    await Timer(5, "ns")
    dut.clk_i.value = 1;
    await Timer(5, "ns")
    dut.clk_i.value = 0;

    await Timer(5, "ns")
    dut.clk_i.value = 1;
    await Timer(5, "ns")
    dut.clk_i.value = 0;

    dut.tx_valid_i.value = 1;
    dut.tx_data_i.value = 100;

    await Timer(5, "ns")
    dut.clk_i.value = 1;
    await Timer(5, "ns")
    dut.clk_i.value = 0;
    dut.tx_valid_i.value = 0;

    for cycle in range(1, 100):
        dut.clk_i.value = 1;
        await Timer(5, "ns")
        dut.clk_i.value = 0;
        await Timer(5, "ns")

A hdl_spi/vhdl_ls.toml => hdl_spi/vhdl_ls.toml +7 -0
@@ 0,0 1,7 @@
# What standard to use. This is optional and defaults to VHDL2008.
standard = "2008"
[libraries]
spi.files = [
    'src/*.vhd',
    'src/**/*.vhd',
]
\ No newline at end of file

Do not follow this link