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

Subversion Repositories neorv32

[/] [neorv32/] [trunk/] [rtl/] [core/] [neorv32_trng.vhd] - Diff between revs 66 and 68

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

Rev 66 Rev 68
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 several ring oscillators as  #
-- # This processor module instantiates the "neoTRNG" true random number generator.                #
-- # entropy source. The outputs of all chains are XORed and de-biased using a John von Neumann    #
-- # See the neoTRNG's documentation for more information: https://github.com/stnolting/neoTRNG    #
-- # randomness extractor. The de-biased signal is further processed by a simple LFSR for improved #
 
-- # whitening.                                                                                    #
 
-- # ********************************************************************************************* #
-- # ********************************************************************************************* #
-- # BSD 3-Clause License                                                                          #
-- # BSD 3-Clause License                                                                          #
-- #                                                                                               #
-- #                                                                                               #
-- # Copyright (c) 2021, Stephan Nolting. All rights reserved.                                     #
-- # Copyright (c) 2021, Stephan Nolting. All rights reserved.                                     #
-- #                                                                                               #
-- #                                                                                               #
Line 57... Line 55...
  );
  );
end neorv32_trng;
end neorv32_trng;
 
 
architecture neorv32_trng_rtl of neorv32_trng is
architecture neorv32_trng_rtl of neorv32_trng is
 
 
  -- Advanced Configuration --------------------------------------------------------------------------------
  -- neoTRNG Configuration -------------------------------------------------------------------------------------------
  constant num_roscs_c     : natural := 4; -- total number of ring oscillators
  constant num_cells_c     : natural := 3; -- total number of ring-oscillator cells
  constant num_inv_start_c : natural := 5; -- number of inverters in FIRST ring oscillator (has to be odd)
  constant num_inv_start_c : natural := 3; -- number of inverters in first cell (short path), has to be odd
  constant num_inv_inc_c   : natural := 2; -- number of inverters increment for each next ring oscillator (has to be even)
  constant num_inv_inc_c   : natural := 2; -- number of additional inverters in next cell (short path), has to be even
  constant lfsr_en_c       : boolean := true; -- use LFSR-based post-processing
  constant num_inv_delay_c : natural := 2; -- additional inverters to form cell's long path, has to be even
  constant lfsr_taps_c     : std_ulogic_vector(7 downto 0) := "10111000"; -- Fibonacci post-processing LFSR feedback taps
  -- -----------------------------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------------------
 
 
 
  -- control register bits --
  -- control register bits --
  constant ctrl_data_lsb_c : natural :=  0; -- r/-: Random data byte LSB
  constant ctrl_data_lsb_c : natural :=  0; -- r/-: Random data byte LSB
  constant ctrl_data_msb_c : natural :=  7; -- r/-: Random data byte MSB
  constant ctrl_data_msb_c : natural :=  7; -- r/-: Random data byte MSB
  --
 
  constant ctrl_en_c       : natural := 30; -- r/w: TRNG enable
  constant ctrl_en_c       : natural := 30; -- r/w: TRNG enable
  constant ctrl_valid_c    : natural := 31; -- r/-: Output data valid
  constant ctrl_valid_c    : natural := 31; -- r/-: Output data 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: Ring-Oscillator --
 
  component neorv32_trng_ring_osc
 
    generic (
 
      NUM_INV : natural := 16 -- number of inverters in chain
 
    );
 
    port (
 
      clk_i    : in  std_ulogic;
 
      enable_i : in  std_ulogic; -- enable chain input
 
      enable_o : out std_ulogic; -- enable chain output
 
      data_o   : out std_ulogic  -- sync random bit
 
    );
 
  end component;
 
 
 
  -- access control --
  -- access control --
  signal acc_en : std_ulogic; -- module access enable
  signal acc_en : std_ulogic; -- module access enable
  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
 
 
  -- ring-oscillator array --
  -- Component: neoTRNG true random number generator --
  signal osc_array_en_in  : std_ulogic_vector(num_roscs_c-1 downto 0);
  component neoTRNG
  signal osc_array_en_out : std_ulogic_vector(num_roscs_c-1 downto 0);
    generic (
  signal osc_array_data   : std_ulogic_vector(num_roscs_c-1 downto 0);
      NUM_CELLS     : natural; -- total number of ring-oscillator cells
 
      NUM_INV_START : natural; -- number of inverters in first cell (short path), has to be odd
  -- von-Neumann de-biasing --
      NUM_INV_INC   : natural; -- number of additional inverters in next cell (short path), has to be even
  type debiasing_t is record
      NUM_INV_DELAY : natural  -- additional inverters to form cell's long path, has to be even
    sreg  : std_ulogic_vector(1 downto 0);
    );
    state : std_ulogic; -- process de-biasing every second cycle
    port (
    valid : std_ulogic; -- de-biased data
      clk_i    : in  std_ulogic; -- global clock line
    data  : std_ulogic; -- de-biased data valid
      enable_i : in  std_ulogic; -- unit enable (high-active), reset unit when low
  end record;
      data_o   : out std_ulogic_vector(7 downto 0); -- random data byte output
  signal debiasing : debiasing_t;
      valid_o  : out std_ulogic  -- data_o is valid when set
 
    );
 
  end component;
 
 
  -- (post-)processing core --
  -- TRNG interface --
  type processing_t is record
  signal trng_data  : std_ulogic_vector(7 downto 0);
    enable : std_ulogic; -- TRNG enable flag
  signal trng_valid : std_ulogic;
    cnt    : std_ulogic_vector(3 downto 0); -- bit counter
 
    sreg   : std_ulogic_vector(7 downto 0); -- data shift register
  -- arbiter --
    output : std_ulogic_vector(7 downto 0); -- output register
  signal enable  : std_ulogic;
    valid  : std_ulogic; -- data output valid flag
  signal valid   : std_ulogic;
  end record;
  signal rnd_reg : std_ulogic_vector(7 downto 0);
  signal processing : processing_t;
 
 
 
begin
begin
 
 
  -- Sanity Checks --------------------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  assert not (num_roscs_c = 0) report "NEORV32 PROCESSOR CONFIG ERROR: TRNG - Total number of ring-oscillators has to be >0." severity error;
 
  assert not ((num_inv_start_c mod 2)  = 0) report "NEORV32 PROCESSOR CONFIG ERROR: TRNG - Number of inverters in first ring has to be odd." severity error;
 
  assert not ((num_inv_inc_c   mod 2) /= 0) report "NEORV32 PROCESSOR CONFIG ERROR: TRNG - Number of inverters increment for each next ring has to be even." severity error;
 
 
 
 
 
  -- Access Control -------------------------------------------------------------------------
  -- Access Control -------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  acc_en <= '1' when (addr_i(hi_abb_c downto lo_abb_c) = trng_base_c(hi_abb_c downto lo_abb_c)) else '0';
  acc_en <= '1' when (addr_i(hi_abb_c downto lo_abb_c) = trng_base_c(hi_abb_c downto lo_abb_c)) else '0';
  wren   <= acc_en and wren_i;
  wren   <= acc_en and wren_i;
  rden   <= acc_en and rden_i;
  rden   <= acc_en and rden_i;
Line 139... Line 116...
  -- Read/Write Access ----------------------------------------------------------------------
  -- Read/Write Access ----------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  rw_access: process(clk_i)
  rw_access: process(clk_i)
  begin
  begin
    if rising_edge(clk_i) then
    if rising_edge(clk_i) then
 
      -- host bus acknowledge --
      ack_o <= wren or rden;
      ack_o <= wren or rden;
 
 
      -- write access --
      -- write access --
      if (wren = '1') then
      if (wren = '1') then
        processing.enable <= data_i(ctrl_en_c);
        enable <= data_i(ctrl_en_c);
      end if;
      end if;
 
 
      -- read access --
      -- read access --
      data_o <= (others => '0');
      data_o <= (others => '0');
      if (rden = '1') then
      if (rden = '1') then
        data_o(ctrl_data_msb_c downto ctrl_data_lsb_c) <= processing.output;
        data_o(ctrl_data_msb_c downto ctrl_data_lsb_c) <= rnd_reg;
        data_o(ctrl_en_c)                              <= processing.enable;
        data_o(ctrl_en_c)    <= enable;
        data_o(ctrl_valid_c)                           <= processing.valid;
        data_o(ctrl_valid_c) <= valid;
 
      end if;
 
 
 
      -- sample --
 
      if (trng_valid = '1') then
 
        rnd_reg <= trng_data;
 
      end if;
 
 
 
      -- data valid? --
 
      if (enable = '0') then -- disabled
 
        valid <= '0';
 
      else
 
        if (trng_valid = '1') then
 
          valid <= '1';
 
        elsif (rden = '1') then
 
          valid <= '0';
 
        end if;
      end if;
      end if;
    end if;
    end if;
  end process rw_access;
  end process rw_access;
 
 
 
 
 
  -- neoTRNG --------------------------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  neoTRNG_inst: neoTRNG
 
    generic map (
 
      NUM_CELLS     => num_cells_c,
 
      NUM_INV_START => num_inv_start_c,
 
      NUM_INV_INC   => num_inv_inc_c,
 
      NUM_INV_DELAY => num_inv_delay_c
 
    )
 
    port map (
 
      clk_i    => clk_i,
 
      enable_i => enable,
 
      data_o   => trng_data,
 
      valid_o  => trng_valid
 
    );
 
 
 
 
 
end neorv32_trng_rtl;
 
 
 
 
 
-- ############################################################################################################################
 
-- ############################################################################################################################
 
 
 
 
 
-- #################################################################################################
 
-- # << neoTRNG - A Tiny and Platform-Independent True Random Number Generator for any FPGA >>     #
 
-- # ********************************************************************************************* #
 
-- # This generator is based on entropy cells, which implement simple ring-oscillators. Each ring- #
 
-- # oscillator features a short and a long delay path that is dynamically selected defining the   #
 
-- # primary oscillation frequency. The cells are cascaded so that the random data output of a     #
 
-- # cell controls the delay path of the next cell (which has the next-larger inverter chain).     #
 
-- #                                                                                               #
 
-- # The random data outputs of all cells are XOR-ed and de-biased using a von Neumann randomness  #
 
-- # extractor (converting edges into bits). The resulting bit is sampled in chunks of 8 bits to   #
 
-- # provide the final random data output. No further internal post-processing is applied. Hence,  #
 
-- # the TRNG produces simple de-biased *RAW* data.                                                #
 
-- #                                                                                               #
 
-- # The entropy cell architecture uses individually-controlled latches and inverters to create    #
 
-- # the inverter chain in a platform-agnostic style that can be implemented for any FPGA without  #
 
-- # requiring primitive instantiation or technology-specific attributes.                          #
 
-- #                                                                                               #
 
-- # See the neoTRNG's documentation for more information: https://github.com/stnolting/neoTRNG    #
 
-- # ********************************************************************************************* #
 
-- # BSD 3-Clause License                                                                          #
 
-- #                                                                                               #
 
-- # Copyright (c) 2021, 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.                                                            #
 
-- # ********************************************************************************************* #
 
-- # neoTRNG - https://github.com/stnolting/neoTRNG                            (c) Stephan Nolting #
 
-- #################################################################################################
 
 
 
library ieee;
 
use ieee.std_logic_1164.all;
 
use ieee.numeric_std.all;
 
 
 
entity neoTRNG is
 
  generic (
 
    NUM_CELLS     : natural; -- total number of ring-oscillator cells
 
    NUM_INV_START : natural; -- number of inverters in first cell (short path), has to be odd
 
    NUM_INV_INC   : natural; -- number of additional inverters in next cell (short path), has to be even
 
    NUM_INV_DELAY : natural  -- additional inverters to form cell's long path, has to be even
 
  );
 
  port (
 
    clk_i    : in  std_ulogic; -- global clock line
 
    enable_i : in  std_ulogic; -- unit enable (high-active), reset unit when low
 
    data_o   : out std_ulogic_vector(7 downto 0); -- random data byte output
 
    valid_o  : out std_ulogic  -- data_o is valid when set
 
  );
 
end neoTRNG;
 
 
 
architecture neoTRNG_rtl of neoTRNG is
 
 
 
  -- Component: neoTRNG entropy cell --
 
  component neoTRNG_cell
 
    generic (
 
      NUM_INV_S : natural; -- number of inverters in short path
 
      NUM_INV_L : natural  -- number of inverters in long path
 
    );
 
    port (
 
      clk_i    : in  std_ulogic; -- system clock
 
      select_i : in  std_ulogic; -- delay select
 
      enable_i : in  std_ulogic; -- enable chain input
 
      enable_o : out std_ulogic; -- enable chain output
 
      data_o   : out std_ulogic  -- sync random bit
 
    );
 
  end component;
 
 
 
  -- ring-oscillator array interconnect --
 
  type cell_array_t is record
 
    en_in  : std_ulogic_vector(NUM_CELLS-1 downto 0);
 
    en_out : std_ulogic_vector(NUM_CELLS-1 downto 0);
 
    rnd    : std_ulogic_vector(NUM_CELLS-1 downto 0);
 
    sel    : std_ulogic_vector(NUM_CELLS-1 downto 0);
 
  end record;
 
  signal cell_array : cell_array_t;
 
 
 
  -- global cell-XOR --
 
  signal rnd_bit : std_ulogic;
 
 
 
  -- von-Neumann de-biasing --
 
  type debiasing_t is record
 
    sreg  : std_ulogic_vector(1 downto 0);
 
    state : std_ulogic; -- process de-biasing every second cycle
 
    valid : std_ulogic; -- de-biased data
 
    data  : std_ulogic; -- de-biased data valid
 
  end record;
 
  signal deb : debiasing_t;
 
 
 
  -- control unit --
 
  type ctrl_t is record
 
    enable : std_ulogic;
 
    run    : std_ulogic;
 
    cnt    : std_ulogic_vector(2 downto 0); -- bit counter
 
    sreg   : std_ulogic_vector(7 downto 0); -- data shift register
 
  end record;
 
  signal ctrl : ctrl_t;
 
 
 
begin
 
 
 
  -- Sanity Checks --------------------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  assert not (NUM_CELLS < 2) report "neoTRNG config ERROR: Total number of ring-oscillator cells <NUM_CELLS> has to be >= 2." severity error;
 
  assert not ((NUM_INV_START mod 2)  = 0) report "neoTRNG config ERROR: Number of inverters in first cell <NUM_INV_START> has to be odd." severity error;
 
  assert not ((NUM_INV_INC   mod 2) /= 0) report "neoTRNG config ERROR: Inverter increment for each next cell <NUM_INV_INC> has to be even." severity error;
 
  assert not ((NUM_INV_DELAY mod 2) /= 0) report "neoTRNG config ERROR: Inverter increment to form long path <NUM_INV_DELAY> has to be even." severity error;
 
 
 
 
  -- Entropy Source -------------------------------------------------------------------------
  -- Entropy Source -------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  neorv32_trng_ring_osc_inst:
  neoTRNG_cell_inst:
  for i in 0 to num_roscs_c-1 generate
  for i in 0 to NUM_CELLS-1 generate
    neorv32_trng_ring_osc_inst_i: neorv32_trng_ring_osc
    neoTRNG_cell_inst_i: neoTRNG_cell
    generic map (
    generic map (
      NUM_INV => num_inv_start_c + (i*num_inv_inc_c) -- number of inverters in chain
      NUM_INV_S => NUM_INV_START + (i*NUM_INV_INC), -- number of inverters in short chain
 
      NUM_INV_L => NUM_INV_START + (i*NUM_INV_INC) + NUM_INV_DELAY -- number of inverters in long chain
    )
    )
    port map (
    port map (
      clk_i    => clk_i,
      clk_i    => clk_i,
      enable_i => osc_array_en_in(i),
      select_i => cell_array.sel(i),
      enable_o => osc_array_en_out(i),
      enable_i => cell_array.en_in(i),
      data_o   => osc_array_data(i)
      enable_o => cell_array.en_out(i),
 
      data_o   => cell_array.rnd(i) -- SYNC data output
    );
    );
  end generate;
  end generate;
 
 
  -- RO enable chain --
  -- path select chain --
  array_intercon: process(processing.enable, osc_array_en_out)
  cell_array.sel(0) <= cell_array.rnd(NUM_CELLS-1); -- use output of last cell to select path of first cell
 
  cell_array.sel(NUM_CELLS-1 downto 1) <= cell_array.rnd(NUM_CELLS-2 downto 0); -- i+1 <= i
 
 
 
  -- enable chain --
 
  cell_array.en_in(0) <= ctrl.enable; -- start of chain
 
  cell_array.en_in(NUM_CELLS-1 downto 1) <=cell_array.en_out(NUM_CELLS-2 downto 0); -- i+1 <= i
 
 
 
 
 
  -- XOR All Cell's Outputs -----------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  cell_xor: process(cell_array.rnd)
 
    variable tmp_v : std_ulogic;
  begin
  begin
    for i in 0 to num_roscs_c-1 loop
    tmp_v := '0';
      if (i = 0) then -- start of enable chain
    for i in 0 to NUM_CELLS-1 loop
        osc_array_en_in(i) <= processing.enable;
      tmp_v := tmp_v xor cell_array.rnd(i);
      else
 
        osc_array_en_in(i) <= osc_array_en_out(i-1);
 
      end if;
 
    end loop; -- i
    end loop; -- i
  end process array_intercon;
    rnd_bit <= tmp_v;
 
  end process cell_xor;
 
 
 
 
  -- John von Neumann De-Biasing ------------------------------------------------------------
  -- John von Neumann Randomness Extractor --------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  neumann_debiasing_sync: process(clk_i)
  debiasing_sync: process(clk_i)
  begin
  begin
    if rising_edge(clk_i) then
    if rising_edge(clk_i) then
      debiasing.sreg  <= debiasing.sreg(debiasing.sreg'left-1 downto 0) & xor_reduce_f(osc_array_data);
      deb.sreg <= deb.sreg(0) & rnd_bit;
      debiasing.state <= (not debiasing.state) and osc_array_en_out(num_roscs_c-1); -- start toggling when last RO is enabled -> process in every second cycle
      -- start operation when last cell is enabled and process in every second cycle --
 
      deb.state <= (not deb.state) and cell_array.en_out(NUM_CELLS-1);
    end if;
    end if;
  end process neumann_debiasing_sync;
  end process debiasing_sync;
 
 
  -- Edge detector --
  -- edge detector --
  neumann_debiasing_comb: process(debiasing)
  debiasing_comb: process(deb)
    variable tmp_v : std_ulogic_vector(2 downto 0);
    variable tmp_v : std_ulogic_vector(2 downto 0);
  begin
  begin
    -- check groups of two non-overlapping bits from the input stream
    tmp_v := deb.state & deb.sreg(1 downto 0); -- check groups of two non-overlapping bits from the input stream
    tmp_v := debiasing.state & debiasing.sreg;
 
    case tmp_v is
    case tmp_v is
      when "101"  => debiasing.valid <= '1'; debiasing.data <= '1'; -- rising edge  -> '1'
      when "101"  => deb.valid <= '1'; deb.data <= '0'; -- rising edge = '0'
      when "110"  => debiasing.valid <= '1'; debiasing.data <= '0'; -- falling edge -> '0'
      when "110"  => deb.valid <= '1'; deb.data <= '1'; -- falling edge = '1'
      when others => debiasing.valid <= '0'; debiasing.data <= '0'; -- no valid data
      when others => deb.valid <= '0'; deb.data <= '-'; -- no valid data
    end case;
    end case;
  end process neumann_debiasing_comb;
  end process debiasing_comb;
 
 
 
 
  -- Processing Core ------------------------------------------------------------------------
  -- Control Unit ---------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  processing_core: process(clk_i)
  control_unit: process(clk_i)
  begin
  begin
    if rising_edge(clk_i) then
    if rising_edge(clk_i) then
      -- sample random data bit and apply post-processing --
      -- make sure enable is sync --
      if (processing.enable = '0') then
      ctrl.enable <= enable_i;
        processing.cnt  <= (others => '0');
 
        processing.sreg <= (others => '0');
 
      elsif (debiasing.valid = '1') then -- valid random sample?
 
        if (processing.cnt = "1000") then
 
          processing.cnt <= (others => '0');
 
        else
 
          processing.cnt <= std_ulogic_vector(unsigned(processing.cnt) + 1);
 
        end if;
 
        if (lfsr_en_c = true) then -- LFSR post-processing
 
          processing.sreg <= processing.sreg(processing.sreg'left-1 downto 0) & ((not xor_reduce_f(processing.sreg and lfsr_taps_c)) xnor debiasing.data);
 
        else -- NO post-processing
 
          processing.sreg <= processing.sreg(processing.sreg'left-1 downto 0) & debiasing.data;
 
        end if;
 
      end if;
 
 
 
      -- data output register --
      -- sample chunks of 8 bit --
      if (processing.cnt = "1000") then
      if (ctrl.enable = '0') then
        processing.output <= processing.sreg;
        ctrl.cnt <= (others => '0');
 
        ctrl.run <= '0';
 
      elsif (deb.valid = '1') then -- valid random sample?
 
        ctrl.cnt <= std_ulogic_vector(unsigned(ctrl.cnt) + 1);
 
        ctrl.run <= '1';
      end if;
      end if;
 
 
      -- data ready/valid flag --
      -- sample shift register --
      if (processing.cnt = "1000") then -- new sample ready?
      if (deb.valid = '1') then
        processing.valid <= '1';
        ctrl.sreg <= ctrl.sreg(ctrl.sreg'left-1 downto 0) & deb.data;
      elsif (processing.enable = '0') or (rden = '1') then -- clear when deactivated or on data read
 
        processing.valid <= '0';
 
      end if;
      end if;
 
 
    end if;
    end if;
  end process processing_core;
  end process control_unit;
 
 
 
  -- random byte output --
 
  data_o <= ctrl.sreg;
 
 
 
  -- data valid? --
 
  valid_o <= '1' when (ctrl.cnt = "000") and (ctrl.run = '1') else '0';
 
 
end neorv32_trng_rtl;
 
 
end neoTRNG_rtl;
 
 
 
 
-- ############################################################################################################################
-- ############################################################################################################################
-- ############################################################################################################################
-- ############################################################################################################################
 
 
 
 
-- #################################################################################################
-- #################################################################################################
-- # << NEORV32 - True Random Number Generator (TRNG) - Ring-Oscillator-Based Entropy Source >>    #
-- # << neoTRNG - A Tiny and Platform-Independent True Random Number Generator for any FPGA >>     #
-- # ********************************************************************************************* #
-- # ********************************************************************************************* #
-- # An inverter chain (ring oscillator) is used as entropy source.                                #
-- # neoTRNG Entropy Cell                                                                          #
-- # The inverter chain is constructed as an "asynchronous" LFSR. The single inverters are         #
-- #                                                                                               #
-- # connected via latches that are used to enable/disable the TRNG. Also, these latches are used  #
-- # The cell consists of two ring-oscillators build from inverter chains. The short chain uses    #
-- # as additional delay element. By using unique enable signals for each latch, the synthesis     #
-- # NUM_INV_S inverters and oscillates at a "high" frequency and the long chain uses NUM_INV_L    #
-- # tool cannot "optimize" (=remove) any of the inverters out of the design.                      #
-- # inverters and oscillates at a "low" frequency. The select_i input selects which chain is      #
 
-- # actually used.                                                                                #
 
-- #                                                                                               #
 
-- # Each inverter chain is constructed as an "asynchronous" shift register. The single inverters  #
 
-- # are connected via latches that are used to enable/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 making the  #
 
-- # design platform-agnostic.                                                                     #
-- # ********************************************************************************************* #
-- # ********************************************************************************************* #
-- # BSD 3-Clause License                                                                          #
-- # BSD 3-Clause License                                                                          #
-- #                                                                                               #
-- #                                                                                               #
-- # Copyright (c) 2021, Stephan Nolting. All rights reserved.                                     #
-- # Copyright (c) 2021, Stephan Nolting. All rights reserved.                                     #
-- #                                                                                               #
-- #                                                                                               #
Line 289... Line 448...
-- # GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED    #
-- # 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     #
-- # 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  #
-- # NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED  #
-- # OF THE POSSIBILITY OF SUCH DAMAGE.                                                            #
-- # OF THE POSSIBILITY OF SUCH DAMAGE.                                                            #
-- # ********************************************************************************************* #
-- # ********************************************************************************************* #
-- # The NEORV32 Processor - https://github.com/stnolting/neorv32              (c) Stephan Nolting #
-- # neoTRNG - https://github.com/stnolting/neoTRNG                            (c) Stephan Nolting #
-- #################################################################################################
-- #################################################################################################
 
 
library ieee;
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
 
 
 
library neorv32;
 
use neorv32.neorv32_package.all;
 
 
 
entity neorv32_trng_ring_osc is
entity neoTRNG_cell is
  generic (
  generic (
    NUM_INV : natural := 15 -- number of inverters in chain
    NUM_INV_S : natural; -- number of inverters in short path
 
    NUM_INV_L : natural  -- number of inverters in long path
  );
  );
  port (
  port (
    clk_i    : in  std_ulogic;
    clk_i    : in  std_ulogic; -- system clock
 
    select_i : in  std_ulogic; -- delay select
    enable_i : in  std_ulogic; -- enable chain input
    enable_i : in  std_ulogic; -- enable chain input
    enable_o : out std_ulogic; -- enable chain output
    enable_o : out std_ulogic; -- enable chain output
    data_o   : out std_ulogic  -- sync random bit
    data_o   : out std_ulogic  -- sync random bit
  );
  );
end neorv32_trng_ring_osc;
end neoTRNG_cell;
 
 
architecture neorv32_trng_ring_osc_rtl of neorv32_trng_ring_osc is
architecture neoTRNG_cell_rtl of neoTRNG_cell is
 
 
  signal inv_chain   : std_ulogic_vector(NUM_INV-1 downto 0); -- oscillator chain
  signal inv_chain_s   : std_ulogic_vector(NUM_INV_S-1 downto 0); -- short oscillator chain
  signal enable_sreg : std_ulogic_vector(NUM_INV-1 downto 0); -- enable shift register
  signal inv_chain_l   : std_ulogic_vector(NUM_INV_L-1 downto 0); -- long oscillator chain
 
  signal feedback      : std_ulogic; -- cell feedback/output
 
  signal enable_sreg_s : std_ulogic_vector(NUM_INV_S-1 downto 0); -- enable shift register for short chain
 
  signal enable_sreg_l : std_ulogic_vector(NUM_INV_L-1 downto 0); -- enable shift register for long chain
  signal sync_ff     : std_ulogic_vector(1 downto 0); -- output signal synchronizer
  signal sync_ff     : std_ulogic_vector(1 downto 0); -- output signal synchronizer
 
 
begin
begin
 
 
  -- Ring Oscillator ------------------------------------------------------------------------
  -- Ring Oscillators -----------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  ring_osc: process(enable_i, enable_sreg, inv_chain)
  -- Each cell provides a short inverter chain (high frequency) and a long oscillator chain (low frequency).
 
  -- The select_i signals defines which chain is enabled.
 
  -- NOTE: All signals that control a inverter-latch element have to be registered to ensure a single element
 
  -- is mapped to a single LUT (or LUT + FF(latch-mode)).
 
 
 
  -- short oscillator chain --
 
  ring_osc_short: process(enable_i, enable_sreg_s, feedback, inv_chain_s)
  begin
  begin
    -- Using individual enable signals for each inverter - derived from a shift register - to prevent the synthesis tool
    for i in 0 to NUM_INV_S-1 loop -- inverters in short chain
    -- from removing all but one inverter (since they implement "logical identical functions").
 
    -- This also allows to make the TRNG platform independent.
 
    for i in 0 to NUM_INV-1 loop -- inverters in chain
 
      if (enable_i = '0') then -- start with a defined state (latch reset)
      if (enable_i = '0') then -- start with a defined state (latch reset)
        inv_chain(i) <= '0';
        inv_chain_s(i) <= '0';
      elsif (enable_sreg(i) = '1') then
      elsif (enable_sreg_s(i) = '1') then
        -- here we have the inverter chain --
        if (i = NUM_INV_S-1) then -- left-most inverter?
        if (i = NUM_INV-1) then -- left-most inverter?
          inv_chain_s(i) <= not feedback;
          inv_chain(i) <= not inv_chain(0);
 
        else
        else
          inv_chain(i) <= not inv_chain(i+1);
          inv_chain_s(i) <= not inv_chain_s(i+1);
        end if;
        end if;
      end if;
      end if;
    end loop; -- i
    end loop; -- i
  end process ring_osc;
  end process ring_osc_short;
 
 
 
  -- long oscillator chain --
 
  ring_osc_long: process(enable_i, enable_sreg_l, feedback, inv_chain_l)
 
  begin
 
    for i in 0 to NUM_INV_L-1 loop -- inverters in long chain
 
      if (enable_i = '0') then -- start with a defined state (latch reset)
 
        inv_chain_l(i) <= '0';
 
      elsif (enable_sreg_l(i) = '1') then
 
        if (i = NUM_INV_L-1) then -- left-most inverter?
 
          inv_chain_l(i) <= not feedback;
 
        else
 
          inv_chain_l(i) <= not inv_chain_l(i+1);
 
        end if;
 
      end if;
 
    end loop; -- i
 
  end process ring_osc_long;
 
 
 
  -- length select --
 
  feedback <= inv_chain_l(0) when (select_i = '0') else inv_chain_s(0);
 
 
 
 
  -- Control --------------------------------------------------------------------------------
  -- Control --------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
 
  -- Using individual enable signals for each inverter from a shift register to prevent the synthesis tool
 
  -- from removing all but one inverter (since they implement "logical identical functions" (='toggle')).
 
  -- This makes the TRNG platform independent (since we do not need to use primitives to ensure a correct architecture).
  ctrl_unit: process(clk_i)
  ctrl_unit: process(clk_i)
  begin
  begin
    if rising_edge(clk_i) then
    if rising_edge(clk_i) then
      enable_sreg <= enable_sreg(enable_sreg'left-1 downto 0) & enable_i; -- activate right-most inverter first
      -- enable sreg --
      sync_ff     <= sync_ff(0) & inv_chain(0); -- synchronize to prevent metastability 
      enable_sreg_s <= enable_sreg_s(enable_sreg_s'left-1 downto 0) & enable_i;
 
      enable_sreg_l <= enable_sreg_l(enable_sreg_l'left-1 downto 0) & enable_sreg_s(enable_sreg_s'left);
 
      -- data output sync - no metastability beyond this point --
 
      sync_ff <= sync_ff(0) & feedback;
    end if;
    end if;
  end process ctrl_unit;
  end process ctrl_unit;
 
 
  -- output for "enable chain" --
  -- output for "enable chain" --
  enable_o <= enable_sreg(enable_sreg'left);
  enable_o <= enable_sreg_l(enable_sreg_l'left);
 
 
  -- rnd output --
  -- random data output --
  data_o <= sync_ff(1);
  data_o <= sync_ff(1);
 
 
 
 
end neorv32_trng_ring_osc_rtl;
end neoTRNG_cell_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.