OpenCores
URL https://opencores.org/ocsvn/neorv32/neorv32/trunk

Subversion Repositories neorv32

[/] [neorv32/] [trunk/] [rtl/] [core/] [neorv32_trng.vhd] - Diff between revs 22 and 23

Go to most recent revision | Show entire file | Details | Blame | View Log

Rev 22 Rev 23
Line 1... Line 1...
-- #################################################################################################
-- #################################################################################################
-- # << NEORV32 - True Random Number Generator (TRNG) >>                                           #
-- # << NEORV32 - True Random Number Generator (TRNG) >>                                           #
-- # ********************************************************************************************* #
-- # ********************************************************************************************* #
-- # This unit implements a true random number generator which uses an inverter chain as entropy   #
-- # This unit implements a true random number generator which uses several GARO chain as entropy  #
-- # source. The inverter chain is constructed as GARO (Galois Ring Oscillator) TRNG. The single   #
-- # source. The outputs of all chains are XORed and de-biased using a John von Neumann randomness #
-- # inverters are connected via simple latches that are used to enbale/disable the TRNG. Also,    #
-- # extractor. The de-biased signal is further processed by a simple LFSR for improved whitening. #
-- # these latches are used as additional delay element. By using unique enable signals for each   #
 
-- # latch, the synthesis tool cannot "optimize" one of the inverters out of the design. Further-  #
 
-- # more, the latches prevent the synthesis tool from detecting combinatorial loops.              #
 
-- # The output of the GARO is de-biased by a simple von Neuman random extractor and is further    #
 
-- # post-processed by a 16-bit LFSR for improved whitening.                                       #
 
-- #                                                                                               #
-- #                                                                                               #
-- # Sources:                                                                                      #
-- # Sources:                                                                                      #
-- #  - GARO: "Experimental Assessment of FIRO- and GARO-based Noise Sources for Digital TRNG      #
 
-- #    Designs on FPGAs" by Martin Schramm, Reiner Dojen and Michael Heigly, 2017                 #
 
-- #  - Latches for platform independence: "Extended Abstract: The Butterfly PUF Protecting IP     #
 
-- #    on every FPGA" by Sandeep S. Kumar, Jorge Guajardo, Roel Maesyz, Geert-Jan Schrijen and    #
 
-- #    Pim Tuyls, Philips Research Europe, 2008                                                   #
 
-- #  - Von Neumann De-Biasing: "Iterating Von Neumann's Post-Processing under Hardware            #
-- #  - Von Neumann De-Biasing: "Iterating Von Neumann's Post-Processing under Hardware            #
-- #    Constraints" by Vladimir Rozic, Bohan Yang, Wim Dehaene and Ingrid Verbauwhede, 2016       #
-- #    Constraints" by Vladimir Rozic, Bohan Yang, Wim Dehaene and Ingrid Verbauwhede, 2016       #
-- # ********************************************************************************************* #
-- # ********************************************************************************************* #
-- # BSD 3-Clause License                                                                          #
-- # BSD 3-Clause License                                                                          #
-- #                                                                                               #
-- #                                                                                               #
Line 71... Line 61...
end neorv32_trng;
end neorv32_trng;
 
 
architecture neorv32_trng_rtl of neorv32_trng is
architecture neorv32_trng_rtl of neorv32_trng is
 
 
  -- advanced configuration --------------------------------------------------------------------------------
  -- advanced configuration --------------------------------------------------------------------------------
  constant num_inv_c   : natural := 16; -- length of GARO inverter chain (default=16, max=16)
  constant num_inv_c   : natural := 15; -- length of GARO inverter chain (default=15, has to be odd)
  constant lfsr_taps_c : std_ulogic_vector(15 downto 0) := "1101000000001000"; -- Fibonacci LFSR feedback taps
  constant num_garos_c : natural := 2; -- number of GARO elements (default=2)
 
  constant lfsr_taps_c : std_ulogic_vector(7 downto 0) := "10111000"; -- Fibonacci post-processing LFSR feedback taps
 
  constant lfsr_en_c   : boolean := true; -- use LFSR-based post-processing
 
  type tap_mask_t is array (0 to num_garos_c-1) of std_ulogic_vector(num_inv_c-2 downto 0);
 
  constant tap_mask : tap_mask_t := ( -- GARO tap masks, sum of set bits has to be even
 
    "11110000000000",
 
    "00000011000000"
 
  );
  -- -------------------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------------------
 
 
  -- control register bits --
  -- control register bits --
  constant ctrl_taps_lsb_c  : natural :=  0; -- -/w: TAP 0 enable
  constant ctrl_data_lsb_c   : natural :=  0; -- r/-: Random data bit LSB
  constant ctrl_taps_msb_c  : natural := 15; -- -/w: TAP 15 enable
  constant ctrl_data_msb_c   : natural :=  7; -- r/-: Random data bit MSB
 
  constant ctrl_data_valid_c : natural := 15; -- r/-: Output data valid
 
  constant ctrl_err_zero_c   : natural := 16; -- r/-: stuck at 0 error
 
  constant ctrl_err_one_c    : natural := 17; -- r/-: stuck at 1 error
  constant ctrl_en_c        : natural := 31; -- r/w: TRNG enable
  constant ctrl_en_c        : natural := 31; -- r/w: TRNG enable
 
 
  -- data register bits --
 
  constant ctrl_data_lsb_c  : natural :=  0; -- r/-: Random data bit 0
 
  constant ctrl_data_msb_c  : natural := 15; -- r/-: Random data bit 15
 
  constant ctrl_rnd_valid_c : natural := 31; -- r/-: Output byte valid
 
 
 
  -- IO space: module base address --
  -- IO space: module base address --
  constant hi_abb_c : natural := index_size_f(io_size_c)-1; -- high address boundary bit
  constant hi_abb_c : natural := index_size_f(io_size_c)-1; -- high address boundary bit
  constant lo_abb_c : natural := index_size_f(trng_size_c); -- low address boundary bit
  constant lo_abb_c : natural := index_size_f(trng_size_c); -- low address boundary bit
 
 
 
  -- Component: GARO Element --
 
  component neorv32_trng_garo_element
 
    generic (
 
      NUM_INV : natural := 16 -- number of inverters in chain
 
    );
 
    port (
 
      clk_i    : in  std_ulogic;
 
      enable_i : in  std_ulogic;
 
      enable_o : out std_ulogic;
 
      mask_i   : in  std_ulogic_vector(NUM_INV-2 downto 0);
 
      data_o   : out std_ulogic;
 
      error0_o : out std_ulogic;
 
      error1_o : out std_ulogic
 
    );
 
  end component;
 
 
  -- access control --
  -- access control --
  signal acc_en : std_ulogic; -- module access enable
  signal acc_en : std_ulogic; -- module access enable
  signal addr   : std_ulogic_vector(31 downto 0); -- access address
  signal addr   : std_ulogic_vector(31 downto 0); -- access address
  signal wren   : std_ulogic; -- full word write enable
  signal wren   : std_ulogic; -- full word write enable
  signal rden   : std_ulogic; -- read enable
  signal rden   : std_ulogic; -- read enable
 
 
  -- random number generator --
  -- garo array --
  signal rnd_inv         : std_ulogic_vector(num_inv_c-1 downto 0); -- inverter chain
  signal garo_en_in    : std_ulogic_vector(num_garos_c-1 downto 0);
  signal rnd_enable_sreg : std_ulogic_vector(num_inv_c-1 downto 0); -- enable shift register
  signal garo_en_out   : std_ulogic_vector(num_garos_c-1 downto 0);
 
  signal garo_data     : std_ulogic_vector(num_garos_c-1 downto 0);
 
  signal garo_err_zero : std_ulogic_vector(num_garos_c-1 downto 0);
 
  signal garo_err_one  : std_ulogic_vector(num_garos_c-1 downto 0);
 
  signal garo_res      : std_ulogic;
 
  signal garo_err0     : std_ulogic;
 
  signal garo_err1     : std_ulogic;
 
 
 
  -- de-biasing --
 
  signal db_data     : std_ulogic_vector(2 downto 0);
 
  signal db_state    : std_ulogic; -- process de-biasing every second cycle
 
  signal rnd_valid   : std_ulogic;
 
  signal rnd_data    : std_ulogic;
 
 
 
  -- processing core --
  signal rnd_enable      : std_ulogic;
  signal rnd_enable      : std_ulogic;
  signal tap_config      : std_ulogic_vector(15 downto 0);
  signal rnd_cnt    : std_ulogic_vector(3 downto 0);
  signal rnd_sync        : std_ulogic_vector(02 downto 0); -- metastability filter & de-biasing
  signal rnd_sreg   : std_ulogic_vector(7 downto 0);
  signal ready_ff        : std_ulogic; -- new random data available
  signal rnd_output : std_ulogic_vector(7 downto 0);
  signal rnd_sreg        : std_ulogic_vector(15 downto 0); -- sample shift reg
  signal rnd_ready  : std_ulogic;
  signal rnd_cnt         : std_ulogic_vector(04 downto 0);
 
  signal new_sample      : std_ulogic; -- new output byte ready
  -- health check --
  signal rnd_data        : std_ulogic_vector(15 downto 0); -- random data register (read-only)
  signal rnd_error_zero : std_ulogic; -- stuck at zero
 
  signal rnd_error_one  : std_ulogic; -- stuck at one
  -- Randomness extractor (von Neumann De-Biasing) --
 
  signal db_state  : std_ulogic;
 
  signal db_enable : std_ulogic; -- valid data from de-biasing
 
  signal db_data   : std_ulogic; -- actual data from de-biasing
 
 
 
begin
begin
 
 
  -- Access Control -------------------------------------------------------------------------
  -- Access Control -------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
Line 130... Line 151...
  begin
  begin
    if rising_edge(clk_i) then
    if rising_edge(clk_i) then
      ack_o <= acc_en and (rden_i or wren_i);
      ack_o <= acc_en and (rden_i or wren_i);
      -- write access --
      -- write access --
      if (wren = '1') then
      if (wren = '1') then
        if (addr = trng_ctrl_addr_c) then
 
          tap_config <= data_i(tap_config'left downto 0);
 
          rnd_enable <= data_i(ctrl_en_c);
          rnd_enable <= data_i(ctrl_en_c);
        end if;
        end if;
      end if;
 
      -- read access --
      -- read access --
      data_o <= (others => '0');
      data_o <= (others => '0');
      if (rden = '1') then
      if (rden = '1') then
        if (addr = trng_ctrl_addr_c) then
        data_o(ctrl_data_msb_c downto ctrl_data_lsb_c) <= rnd_output;
          data_o(ctrl_taps_msb_c downto ctrl_taps_lsb_c) <= tap_config;
        data_o(ctrl_data_valid_c) <= rnd_ready;
 
        data_o(ctrl_err_zero_c)   <= rnd_error_zero;
 
        data_o(ctrl_err_one_c)    <= rnd_error_one;
          data_o(ctrl_en_c) <= rnd_enable;
          data_o(ctrl_en_c) <= rnd_enable;
        else -- trng_data_addr_c
 
          data_o(ctrl_data_msb_c downto ctrl_data_lsb_c) <= rnd_data;
 
          data_o(ctrl_rnd_valid_c) <= ready_ff;
 
        end if;
 
      end if;
      end if;
    end if;
    end if;
  end process rw_access;
  end process rw_access;
 
 
 
 
  -- True Random Generator ------------------------------------------------------------------
  -- Entropy Source -------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  entropy_source: process(rnd_enable_sreg, rnd_enable, rnd_inv, tap_config)
  neorv32_trng_garo_element_inst:
 
  for i in 0 to num_garos_c-1 generate
 
    neorv32_trng_garo_element_inst_i: neorv32_trng_garo_element
 
    generic map (
 
      NUM_INV => num_inv_c -- number of inverters in chain
 
    )
 
    port map (
 
      clk_i    => clk_i,
 
      enable_i => garo_en_in(i),
 
      enable_o => garo_en_out(i),
 
      mask_i   => tap_mask(i),
 
      data_o   => garo_data(i),
 
      error0_o => garo_err_zero(i),
 
      error1_o => garo_err_one(i)
 
    );
 
  end generate;
 
 
 
  -- GARO element connection --
 
  garo_intercon: process(rnd_enable, garo_en_out, garo_data, garo_err_zero, garo_err_one)
 
    variable data_v : std_ulogic;
 
    variable err0_v : std_ulogic;
 
    variable err1_v : std_ulogic;
  begin
  begin
    for i in 0 to num_inv_c-1 loop
    -- enable chain --
      if (rnd_enable = '0') then -- start with a defined state (latch reset)
    for i in 0 to num_garos_c-1 loop
        rnd_inv(i) <= '0';
      if (i = 0) then
      -- uniquely enable latches to prevent synthesis from removing chain elements
        garo_en_in(i) <= rnd_enable;
      elsif (rnd_enable_sreg(i) = '1') then -- latch enable
 
        -- here we have the inverter chain --
 
        if (i = num_inv_c-1) then -- left most inverter?
 
          if (tap_config(i) = '1') then
 
            rnd_inv(i) <= not rnd_inv(0); -- direct input of right most inverter (= output signal)
 
          else
 
            rnd_inv(i) <= '0';
 
          end if;
 
        else
 
          if (tap_config(i) = '1') then
 
            rnd_inv(i) <= not (rnd_inv(i+1) xor rnd_inv(0)); -- use final output as feedback
 
          else
          else
            rnd_inv(i) <= not rnd_inv(i+1); -- normal chain: use previous inverter's output as input
        garo_en_in(i) <= garo_en_out(i-1);
          end if;
 
        end if;
 
      end if;
      end if;
    end loop; -- i
    end loop; -- i
  end process entropy_source;
    -- data & status --
 
    data_v := garo_data(0);
 
    err0_v := garo_err_zero(0);
 
    err1_v := garo_err_one(0);
 
    for i in 1 to num_garos_c-1 loop
 
      data_v := data_v xor garo_data(i);
 
      err0_v := err0_v or garo_err_zero(i);
 
      err1_v := err1_v or garo_err_one(i);
 
    end loop; -- i
 
    garo_res  <= data_v;
 
    garo_err0 <= err0_v;
 
    garo_err1 <= err1_v;
 
  end process garo_intercon;
 
 
  -- unique enable signals for each inverter latch --
 
  inv_enable: process(clk_i)
  -- De-Biasing -----------------------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  jvn_debiasing_sync: process(clk_i)
  begin
  begin
    if rising_edge(clk_i) then
    if rising_edge(clk_i) then
      -- using individual enable signals for each inverter - derived from a shift register - to prevent the synthesis tool
      db_data  <= db_data(db_data'left-1 downto 0) & garo_res;
      -- from removing all but one inverter (since they implement "logical identical functions")
      db_state <= (not db_state) and rnd_enable; -- just toggle when enabled -> process in every second cycle
      -- this also allows to make the trng platform independent
 
      rnd_enable_sreg <= rnd_enable_sreg(num_inv_c-2 downto 0) & rnd_enable; -- activate right most inverter first
 
    end if;
    end if;
  end process inv_enable;
  end process jvn_debiasing_sync;
 
 
 
 
 
  -- John von Neumann De-Biasing --
 
  jvn_debiasing: process(db_state, db_data)
 
    variable tmp_v : std_ulogic_vector(2 downto 0);
 
  begin
 
    -- check groups of two non-overlapping bits from the input stream
 
    tmp_v := db_state & db_data(db_data'left downto db_data'left-1);
 
    case tmp_v is
 
      when "101"  => rnd_valid <= '1'; rnd_data <= '1'; -- rising edge -> '1'
 
      when "110"  => rnd_valid <= '1'; rnd_data <= '0'; -- falling edge -> '0'
 
      when others => rnd_valid <= '0'; rnd_data <= '-'; -- invalid
 
    end case;
 
  end process jvn_debiasing;
 
 
 
 
  -- Processing Core ------------------------------------------------------------------------
  -- Processing Core ------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  processing_core: process(clk_i)
  processing_core: process(clk_i)
  begin
  begin
    if rising_edge(clk_i) then
    if rising_edge(clk_i) then
      -- synchronize output of GARO --
      -- sample random data and apply post-processing --
      rnd_sync <= rnd_sync(1 downto 0) & rnd_inv(0); -- no more metastability
 
 
 
      -- von Neumann De-Biasing state --
 
      db_state <= (not db_state) and rnd_enable; -- just toggle -> process in every second cycle
 
 
 
      -- sample random data & post-processing --
 
      if (rnd_enable = '0') then
      if (rnd_enable = '0') then
        rnd_cnt  <= (others => '0');
        rnd_cnt  <= (others => '0');
        rnd_sreg <= (others => '0');
        rnd_sreg <= (others => '0');
      elsif (db_enable = '1') then -- valid de-biased output?
      elsif (rnd_valid = '1') and (garo_en_out(garo_en_out'left) = '1') then -- valid random sample and GAROs ready?
        if (rnd_cnt = "10000") then
        if (rnd_cnt = "1000") then
          rnd_cnt <= (others => '0');
          rnd_cnt <= (others => '0');
        else
        else
          rnd_cnt <= std_ulogic_vector(unsigned(rnd_cnt) + 1);
          rnd_cnt <= std_ulogic_vector(unsigned(rnd_cnt) + 1);
        end if;
        end if;
        rnd_sreg <= rnd_sreg(rnd_sreg'left-1 downto 0) & (xnor_all_f(rnd_sreg and lfsr_taps_c) xor db_data); -- LFSR post-processing
        if (lfsr_en_c = true) then -- LFSR post-processing
--      rnd_sreg <= rnd_sreg(rnd_sreg'left-1 downto 0) & db_data; -- LFSR post-processing
          rnd_sreg <= rnd_sreg(rnd_sreg'left-1 downto 0) & (xnor_all_f(rnd_sreg and lfsr_taps_c) xnor rnd_data);
 
        else -- NO post-processing
 
          rnd_sreg <= rnd_sreg(rnd_sreg'left-1 downto 0) & rnd_data;
 
        end if;
      end if;
      end if;
 
 
      -- data output register --
      -- data output register --
      if (new_sample = '1') then
      if (rnd_cnt = "1000") then
        rnd_data <= rnd_sreg;
        rnd_output <= rnd_sreg;
 
      end if;
 
 
 
      -- health check error --
 
      if (rnd_enable = '0') then
 
        rnd_error_zero <= '0';
 
        rnd_error_one  <= '0';
 
      else
 
        rnd_error_zero <= rnd_error_zero or garo_err0;
 
        rnd_error_one  <= rnd_error_one  or garo_err1;
      end if;
      end if;
 
 
      -- data ready flag --
      -- data ready flag --
      if (rnd_enable = '0') or (rden = '1') then -- clear when deactivated or on data read
      if (rnd_cnt = "1000") then -- new sample ready?
        ready_ff <= '0';
        rnd_ready <= '1';
      elsif (new_sample = '1') then
      elsif (rnd_enable = '0') or (rden = '1') then -- clear when deactivated or on data read
        ready_ff <= '1';
        rnd_ready <= '0';
      end if;
      end if;
    end if;
    end if;
  end process processing_core;
  end process processing_core;
 
 
  -- John von Neumann De-Biasing --
 
  debiasing: process(db_state, rnd_sync)
end neorv32_trng_rtl;
    variable tmp_v : std_ulogic_vector(2 downto 0);
 
 
 
 
-- ############################################################################################################################
 
-- ############################################################################################################################
 
 
 
 
 
-- #################################################################################################
 
-- # << NEORV32 - True Random Number Generator (TRNG) - GARO Chain-Based Entropy Source >>         #
 
-- # ********************************************************************************************* #
 
-- # An inverter chain (ring oscillator) is used as entropy source. The inverter chain is          #
 
-- # constructed as GARO (Galois Ring Oscillator) TRNG, which is an "asynchronous" LFSR. The       #
 
-- # single inverters are connected via latches that are used to enbale/disable the TRNG. Also,    #
 
-- # these latches are used as additional delay element. By using unique enable signals for each   #
 
-- # latch, the synthesis tool cannot "optimize" (=remove) any of the inverters out of the design. #
 
-- # Furthermore, the latches prevent the synthesis tool from detecting combinatorial loops.       #
 
-- #                                                                                               #
 
-- # Sources:                                                                                      #
 
-- #  - GARO: "Experimental Assessment of FIRO- and GARO-based Noise Sources for Digital TRNG      #
 
-- #    Designs on FPGAs" by Martin Schramm, Reiner Dojen and Michael Heigly, 2017                 #
 
-- #  - Latches for platform independence: "Extended Abstract: The Butterfly PUF Protecting IP     #
 
-- #    on every FPGA" by Sandeep S. Kumar, Jorge Guajardo, Roel Maesyz, Geert-Jan Schrijen and    #
 
-- #    Pim Tuyls, Philips Research Europe, 2008                                                   #
 
-- # ********************************************************************************************* #
 
-- # BSD 3-Clause License                                                                          #
 
-- #                                                                                               #
 
-- # Copyright (c) 2020, Stephan Nolting. All rights reserved.                                     #
 
-- #                                                                                               #
 
-- # Redistribution and use in source and binary forms, with or without modification, are          #
 
-- # permitted provided that the following conditions are met:                                     #
 
-- #                                                                                               #
 
-- # 1. Redistributions of source code must retain the above copyright notice, this list of        #
 
-- #    conditions and the following disclaimer.                                                   #
 
-- #                                                                                               #
 
-- # 2. Redistributions in binary form must reproduce the above copyright notice, this list of     #
 
-- #    conditions and the following disclaimer in the documentation and/or other materials        #
 
-- #    provided with the distribution.                                                            #
 
-- #                                                                                               #
 
-- # 3. Neither the name of the copyright holder nor the names of its contributors may be used to  #
 
-- #    endorse or promote products derived from this software without specific prior written      #
 
-- #    permission.                                                                                #
 
-- #                                                                                               #
 
-- # THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS   #
 
-- # OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF               #
 
-- # MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE    #
 
-- # COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,     #
 
-- # EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE #
 
-- # GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED    #
 
-- # AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING     #
 
-- # NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED  #
 
-- # OF THE POSSIBILITY OF SUCH DAMAGE.                                                            #
 
-- # ********************************************************************************************* #
 
-- # The NEORV32 Processor - https://github.com/stnolting/neorv32              (c) Stephan Nolting #
 
-- #################################################################################################
 
 
 
library ieee;
 
use ieee.std_logic_1164.all;
 
use ieee.numeric_std.all;
 
 
 
library neorv32;
 
use neorv32.neorv32_package.all;
 
 
 
entity neorv32_trng_garo_element is
 
  generic (
 
    NUM_INV : natural := 15 -- number of inverters in chain
 
  );
 
  port (
 
    clk_i    : in  std_ulogic;
 
    enable_i : in  std_ulogic;
 
    enable_o : out std_ulogic;
 
    mask_i   : in  std_ulogic_vector(NUM_INV-2 downto 0);
 
    data_o   : out std_ulogic;
 
    error0_o : out std_ulogic;
 
    error1_o : out std_ulogic
 
  );
 
end neorv32_trng_garo_element;
 
 
 
architecture neorv32_trng_garo_element_rtl of neorv32_trng_garo_element is
 
 
 
  -- debugging --
 
  constant is_sim_c : boolean := false;
 
 
 
  signal inv_chain   : std_ulogic_vector(NUM_INV-1 downto 0); -- oscillator chain
 
  signal enable_sreg : std_ulogic_vector(NUM_INV-1 downto 0); -- enable shift register
 
  signal sync_ff     : std_ulogic_vector(2 downto 0); -- synchronizer
 
 
 
  signal cnt_zero, cnt_one : std_ulogic_vector(5 downto 0); -- stuck-at-0/1 counters
 
 
  begin
  begin
    -- check groups of two non-overlapping bits from the input stream
 
    tmp_v := db_state & rnd_sync(2 downto 1);
 
    case tmp_v is
 
      when "101"  => db_enable <= '1'; db_data <= '1'; -- rising edge  -> '1'
 
      when "110"  => db_enable <= '1'; db_data <= '0'; -- falling edge -> '0'
 
      when others => db_enable <= '0'; db_data <= '0'; -- invalid
 
    end case;
 
  end process debiasing;
 
 
 
  -- new valid byte available? --
  -- Sanity Check ---------------------------------------------------------------------------
  new_sample <= '1' when (rnd_cnt = "10000") and (rnd_enable = '1') and (db_enable = '1') else '0';
  -- -------------------------------------------------------------------------------------------
 
  assert ((NUM_INV mod 2) /= 0) report "NEORV32 TRNG.GARO_element: NUM_INV has to be odd." severity error;
 
 
 
 
end neorv32_trng_rtl;
  -- Entropy Source -------------------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  garo_chain: process(clk_i, enable_i, enable_sreg, mask_i, inv_chain)
 
  begin
 
    if (is_sim_c = false) then
 
      for i in 0 to NUM_INV-1 loop -- inverters in chain
 
        if (enable_i = '0') then -- start with a defined state (latch reset)
 
          inv_chain(i) <= '0';
 
        -- Using individual enable signals for each inverter - derived from a shift register - to prevent the synthesis tool
 
        -- from removing all but one inverter (since they implement "logical identical functions").
 
        -- This also allows to make the TRNG platform independent.
 
        elsif (enable_sreg(i) = '1') then
 
          -- here we have the inverter chain --
 
          if (i = NUM_INV-1) then -- left-most inverter?
 
            inv_chain(i) <= not inv_chain(0); -- direct input of right most inverter (= output signal)
 
          else
 
            -- if tap switch is ON:  use final output XORed with previous inverter's output
 
            -- if tap switch is OFF: just use previous inverter's output
 
            inv_chain(i) <= not (inv_chain(i+1) xor (inv_chain(0) and mask_i(i)));
 
          end if;
 
        end if;
 
      end loop; -- i
 
    else -- simulate as simple LFSR
 
      if rising_edge(clk_i) then
 
        if (enable_i = '0') then
 
          inv_chain <= (others => '0');
 
        else
 
          inv_chain(NUM_INV-1 downto 0) <= inv_chain(inv_chain'left-1 downto 0) & xnor_all_f(inv_chain(NUM_INV-2 downto 0) and mask_i);
 
        end if;
 
      end if;
 
    end if;
 
  end process garo_chain;
 
 
 
 
 
  -- Control --------------------------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  ctrl_unit: process(clk_i)
 
  begin
 
    if rising_edge(clk_i) then
 
      enable_sreg <= enable_sreg(enable_sreg'left-1 downto 0) & enable_i; -- activate right-most inverter first
 
      sync_ff     <= sync_ff(sync_ff'left-1 downto 0) & inv_chain(0); -- synchronize to prevent metastability 
 
    end if;
 
  end process ctrl_unit;
 
 
 
  -- output for "enable chain" --
 
  enable_o <= enable_sreg(enable_sreg'left);
 
 
 
  -- rnd output --
 
  data_o <= sync_ff(sync_ff'left);
 
 
 
 
 
  -- Health Check ---------------------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  health_check: process(clk_i)
 
  begin
 
    if rising_edge(clk_i) then
 
      if (enable_sreg(enable_sreg'left) = '0') then
 
        cnt_zero <= (others => '0');
 
        cnt_one  <= (others => '0');
 
      else
 
        -- stuck-at-zero --
 
        if (and_all_f(cnt_zero) = '0') then -- max not reached yet
 
          error0_o <= '0';
 
          if (sync_ff(sync_ff'left) = '0') then
 
            cnt_zero <= std_ulogic_vector(unsigned(cnt_zero) + 1);
 
          else
 
            cnt_zero <= (others => '0');
 
          end if;
 
        else
 
          error0_o <= '1';
 
        end if;
 
        -- stuck-at-one --
 
        if (and_all_f(cnt_one) = '0') then -- max not reached yet
 
          error1_o <= '0';
 
          if (sync_ff(sync_ff'left) = '1') then
 
            cnt_one <= std_ulogic_vector(unsigned(cnt_one) + 1);
 
          else
 
            cnt_one <= (others => '0');
 
          end if;
 
        else
 
          error1_o <= '1';
 
        end if;
 
      end if;
 
    end if;
 
  end process health_check;
 
 
 
 
 
end neorv32_trng_garo_element_rtl;
 
 
 No newline at end of file
 No newline at end of file

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.