------------------------------------------------------------
-- Copyright: 2011 Integrated Sytems Laboratory, ETH Zurich
--            http://www.iis.ee.ethz.ch/~sha3
------------------------------------------------------------
-------------------------------------------------------------------------------
-- Title      : Input Block
-- Project    : Shabziger
-------------------------------------------------------------------------------
-- File       : inputblock.vhd
-- Author     : Frank K. Guerkaynak  
-- Company    : Integrated Systems Laboratory, ETH Zurich
-- Created    : 2011-08-16
-- Last update: 2011-09-15
-- Platform   : ModelSim (simulation), Synopsys (synthesis)
-- Standard   : VHDL'87
-------------------------------------------------------------------------------
-- Description: This generates up to 1088 bits for the input
-------------------------------------------------------------------------------
-- Copyright (c) 2011 Integrated Systems Laboratory, ETH Zurich
-------------------------------------------------------------------------------
-- Revisions  :
-- Date        Version  Author  Description
-- 2011-08-16  1.0      kgf	Created
-- 2011-08-31  1.1      kgf     Added some modifications for the GMU_GROESTL
--                              Made a hack for JH, it will delay the FinBlock
--                              by one cycle
-- 2011-09-01  1.2      kgf     Added the FuncScanEnxTI input. This is 1 when
--                              the Shabziger is in configuration mode
-- 2011-09-15  2.0      kgf     Added three more registers to make the backend
--                              a little bit easier
-------------------------------------------------------------------------------

library IEEE;
use IEEE.std_logic_1164.all;
use IEEE.numeric_std.all;             
use work.shabzigerpkg.all;             -- includes constants

entity inputblock is
  
  port (
    AlgSelxSI           : in  std_logic_vector(3 downto 0);
    ClkxCI              : in  std_logic;
    RstxRBI             : in  std_logic;
    FinBlockxSI         : in  std_logic;
    BlockPenUltCyclexSI : in  std_logic;  -- the block has one more cycle,
                                          -- time to act !
    BlockInWrEnxSO      : out std_logic;  -- Handover the current block to out
    BlockFinBlockxSO    : out std_logic;  -- Last block in the message
    FuncScanEnxTI       : in  std_logic;  -- Shabziger is loading configuration
    FuncScanInxTI       : in  std_logic;  -- input of the functional scan
    FuncScanOutxTO      : out std_logic;  -- output of the functional scan
    MsgLenxDO           : out std_logic_vector(63 downto 0);
    DataOutxDO          : out std_logic_vector(1087 downto 0);
    Data2OutxDO         : out std_logic_vector(511 downto 0);
    Data3OutxDO         : out std_logic_vector(511 downto 0);
    Data4OutxDO         : out std_logic_vector(63 downto 0));

end inputblock;

architecture rtl of inputblock is


-------------------------------------------------------------------------------
-- Components
-------------------------------------------------------------------------------  
  component lfsr73
    port (
      ScanInxTI  : in  std_logic;
      ScanEnxTI  : in  std_logic;
      ScanOutxTO : out std_logic;
      DataOutxDO : out std_logic_vector (63 downto 0);
      ClkxCI     : in  std_logic;
      RstxRBI    : in  std_logic);
  end component;

  component padunit
    port (
      DataInxDI  : in  std_logic_vector(1087 downto 0);
      DataOutxDO : out std_logic_vector(1087 downto 0);
      AlgSelxSI  : in  std_logic_vector(3 downto 0);
      DataCntxDI : in  std_logic_vector(63 downto 0));
  end component;
-------------------------------------------------------------------------------
-- Signals 
-------------------------------------------------------------------------------  

-- State machine
  type in_reg_states is (init,first,genvec,send, sleep, g_groestl1, g_groestl2);
  signal StatexDP, StatexDN : in_reg_states;

  
-- LFSR connections
 signal LFSRxD : std_logic_vector(63 downto 0);
 signal LFSRScanOutxT : std_logic;      -- Stitching the scan out chain

-- Signals for determining the Round Cnt, how many LFSR rounds
-- fills the input register
 signal IntAlgSelxS            : integer range 0 to 15;  -- Integer of AlgSelxSI
 signal FinalRndxD             : integer range 0 to 16;  -- Alg dependent
 signal RndCntxDP, RndCntxDN   : integer range 0 to 31;  -- Round Count for
                                                         -- LFSR number kept
                                                         -- high deliberately
                                                         -- normally only up to
                                                         -- 16 will be used.
 signal InitRndxS, RegFullxS   : std_logic;              -- control signals
 signal FinBlockxSN, FinBlockxSP : std_logic;  -- we will keep them in a register

  
-- Padding
 signal PaddedxD : std_logic_vector(1087 downto 0);  -- This is the padded version of the data
 signal SelDataxD : std_logic_vector(1087 downto 0);  -- Either PaddedxD or StoreDataxD will be selected
  
-- DataCounter
-- Count how many bits we have sent.
 signal MsgLenxDP, MsgLenxDN : unsigned(63 downto 0);

  
-- Main signals
-- We now have four registers each driving four algorithms
-- DataxDP is still the main one driving keccak and sha2
-- Data2xDP is 512 bit drives Groestl and Blake
-- Data3xDP is 512 bit drives JH and Skein
-- Data4xDP is 64 bit  drives RAM and Dummy
 signal DataxDP, DataxDN, StoreDataxD : std_logic_vector(1087 downto 0); 
 signal Data2xDP, Data3xDP            : std_logic_vector(511 downto 0);
 signal Data4xDP                      : std_logic_vector(63 downto 0);
 signal EnxS                          : std_logic_vector(16 downto 0);

-- Hack for JH
  -- JH needs one additional cycle for padding. We will use message sizes of
  -- multiples of 512, meaning that there will be a full 512-bit block of padding
  -- always.
  -- In the current inputblock, this does not work, so we add this signal,
  -- which will switch to '1' when the FinalxSI is '1'. But the internal
  -- FinalxS signal will only activate the second time around
  signal JHFinalxSP, JHFinalxSN : std_logic;
  
begin  -- rtl

-------------------------------------------------------------------------------
-- Store the value of FinBlockxSI
-------------------------------------------------------------------------------

-- FinBlockxS also selects normal data or data from the padunit, so it is
-- important that it stays constant throughout block processing
-- We will change it (generally) at the send cycle (exception JH and GMU GROESTL)
  
  p_finblock : process (StatexDP, AlgSelxSI, FinBlockxSP, FinBlockxSI, JHFinalxSP)
  begin  -- process p_finblock
    FinBlockxSN <= FinBlockxSP;         -- by default keep the value
    JHFinalxSN  <= JHFinalxSP;

    ---------------------------------------------------------------------------
    if    (AlgSelxSI = GMUGROESTL) and (StatexDP = g_groestl2) then
          FinBlockxSN <= FinBlockxSI;   -- GMU Groestl waits two cycles
    ---------------------------------------------------------------------------
    elsif (AlgSelxSI = ETHZJH) or (AlgSelxSI = GMUJH) then
        if StatexDP = send then         -- time to decide
          if JHFinalxSP = '1' then      -- do we a pending req
            FinBlockxSN <= '1';         -- activate the final block
            JHFinalxSN  <= '0';         -- clear pending request
          elsif FinBlockxSI = '1' then  -- is there a fin block
            FinBlockxSN <= '0';         -- not this cycle
            JHFinalxSN  <= '1';         -- make sure it will come next cycle
          else
            FinBlockxSN  <= '0';        -- this returns to zero
            JHFinalxSN   <= '0';        -- this stays zero 
          end if;
        end if;
    ---------------------------------------------------------------------------    
    elsif (StatexDP = send) then        -- other algorithms
          FinBlockxSN <= FinBlockxSI;   -- copy FinBlockxSI
    end if;
    ---------------------------------------------------------------------------

    
  end process p_finblock;

--  This was the simpler version GMU GROESTL and SHA 2 will need more cases
--  FinBlockxSN FinBlockxSI when StatexDP = send else FinBlockxSP;
  

  
-------------------------------------------------------------------------------
-- Calculating the RndCnt depending on the Algorithm
-------------------------------------------------------------------------------
  IntAlgSelxS <= to_integer(unsigned(AlgSelxSI));  -- makes life easier
  FinalRndxD  <= NUMROUND(IntAlgSelxS);            -- declared in shabzigerpkg


-- This process calculates the round counter
-- The last round is algorithm dependent 
  p_rnd : process (InitRndxS, RndCntxDP, FinalRndxD)
    begin  -- process p_rnd
      -- defaults 
      RndCntxDN <= RndCntxDP + 1;       -- count rounds up 
      RegFullxS <= '0';
      
      if RndCntxDP = FinalRndxD then    -- we have reached last count
        RegFullxS <= '1';               -- we are done, the reg is full
        RndCntxDN <= RndCntxDP;         -- keep the count
      end if;

      if InitRndxS = '1' then           -- use this signal to initialize
        RndCntxDN <= 0;                 -- set back the round counter
      end if;

    end process p_rnd;

-- This is a simple way of calculating the enable signals
-- based on the round counter
  p_en : process (RndCntxDP, StatexDP)
    begin  -- process p_en
      EnxS <= (others => '0');          -- per default enable nothing
      if StatexDP = genvec then         -- if we are not done with the rounds
        EnxS(RndCntxDP) <= '1';         -- enable only one 64bit block
      end if;
    end process p_en;

-------------------------------------------------------------------------------
-- Generating the control signals
-------------------------------------------------------------------------------

  -- this will not work for some of the blocks we have but it should do well
  -- for the majority of the blocks we have so far.. 
    
  p_cont: process (FinBlockxSP, StatexDP, RegFullxS, BlockPenUltCyclexSI,
                   AlgSelxSI, FuncScanEnxTI)
    begin  -- process p_cont
      -- defaults 
      StatexDN <=  StatexDP;            -- Keep the state
      BlockInWrEnxSO <= '0';              -- Enable the block
      BlockFinBlockxSO <= '0';          -- Signal that this is the last block
      InitRndxS <= '0';                 -- Initialize the round counter
      case StatexDP is
        -----------------------------------------------------------------------
        when init =>
          StatexDN <= first;            -- we need one cycle breather at the
                                        -- beginning.. GMU state machines
                                        -- depend on this
        -----------------------------------------------------------------------
        when first =>
          StatexDN <= genvec;
          InitRndxS        <= '1';
          BlockFinBlockxSO <= '1';
          BlockInWrEnxSO  <= '1';
        -----------------------------------------------------------------------
        when genvec =>
          if RegFullxS='1' then         -- We have the data, let us send it
            StatexDN <= sleep;
          end if;
        -----------------------------------------------------------------------
        when sleep =>                   -- assumes we will always be faster
          if BlockPenUltCyclexSI = '1' then  -- wait till block is ready
            StatexDN <= send;
          end if;
        -----------------------------------------------------------------------
        when send =>
          BlockInWrEnxSO <= '1';          -- Send the data block
          if FinBlockxSP='1' then
            BlockFinBlockxSO <= '1';    -- This is the final block
          end if;

          if AlgSelxSI = GMUGROESTL then
            StatexDN <= g_groestl1;     -- GMU implementation uses two
                                        -- additional cycle constant input
          else
            StatexDN <= genvec;           -- directly generate a new block
            InitRndxS <= '1';             -- clear round counter 
          end if;
        -----------------------------------------------------------------------             
        when g_groestl1 =>              -- first GROESTL GMU sleeper state
            StatexDN <= g_groestl2;           
        -----------------------------------------------------------------------             
        when g_groestl2 =>              -- second gmu groestl sleeper state
            StatexDN <= genvec;           -- directly generate a new block
            InitRndxS <= '1';             -- clear round counter 
        -----------------------------------------------------------------------             
        when others => null;            -- dummy not needed 
      end case;

      -- we stay in init as long as Shabziger is in config mode
      -- This should only follow a reset
      if FuncScanEnxTI = '1' then
        StatexDN <= init;
        BlockInWrEnxSO <= '0';
        BlockFinBlockxSO <= '0';
        InitRndxS <= '0';
      end if;

      
    end process p_cont;


-------------------------------------------------------------------------------
-- The LFSR instantiation
-------------------------------------------------------------------------------
  i_lfsr: lfsr73
    port map (
      ScanInxTI  => FuncScanInxTI,
      ScanEnxTI  => FuncScanEnxTI,
      ScanOutxTO => LFSRScanOutxT,
      DataOutxDO => LFSRxD,
      ClkxCI     => ClkxCI,
      RstxRBI    => RstxRBI);


-------------------------------------------------------------------------------
-- The Data counter (needed for blake, )
-------------------------------------------------------------------------------
 p_data_cnt: process (StatexDP, IntAlgSelxS, MsgLenxDP, RegFullxS, FinBlockxSP, AlgSelxSI)
 begin  -- process p_data_cnt
   MsgLenxDN <= MsgLenxDP;
   if StatexDP = genvec then            -- when we do genvec
     if RegFullxS = '1' then            -- just when we finish the input
       if FinBlockxSP = '1' then      -- Last round or normal round
          MsgLenxDN <= MsgLenxDP + to_unsigned (BITSLASTROUND(IntAlgSelxS),16);
       else
          MsgLenxDN <= MsgLenxDP + to_unsigned (BITSPERROUND(IntAlgSelxS),16);         
       end if;
     end if;
   elsif AlgSelxSI = GMUGROESTL then
     if StatexDP = g_groestl2 and FinBlockxSP = '1'  then
         MsgLenxDN <= (others => '0');    
     end if;  
   elsif StatexDP = send then
     if FinBlockxSP = '1' then
         MsgLenxDN <= (others => '0');
     end if;  
   end if;
 end process p_data_cnt;
    
  MsgLenxDO <= std_logic_vector(MsgLenxDP);             -- final assignment 
    
-------------------------------------------------------------------------------
-- The register holding Input Data
-------------------------------------------------------------------------------

-- handle the LFSR to data transfer
  p_nextdata: process (DataxDP, EnxS, LFSRxD)
  begin  -- process p_nextdata
    StoreDataxD <= DataxDP;                 -- by default don't change
    for i in 0 to 16 loop               -- go through all 17 
      if EnxS(i)='1' then               -- if Enable bit is set
1 downto i*64) <= LFSRxD;  -- copy the value
      end if;
    end loop;  -- i
  end process p_nextdata;


-------------------------------------------------------------------------------
-- Here comes the part that will generate the padding 
-------------------------------------------------------------------------------

  i_padunit: padunit
    port map (
      DataInxDI  => StoreDataxD,
      DataOutxDO => PaddedxD,
      AlgSelxSI   => AlgSelxSI,
      DataCntxDI => std_logic_vector(MsgLenxDP));

   SelDataxD <= PaddedxD when FinBlockxSP = '1' else StoreDataxD;
  
  
-- Add the scan functionality
   DataxDN <= SelDataxD when FuncScanEnxTI = '0' else
              DataxDP(1086 downto 0) & LFSRScanOutxT;
   FuncScanOutxTO <= DataxDP(1087);
  

-- purpose: memorizing process for the registers
  p_clk : process (ClkxCI, RstxRBI)
  begin  -- process p_clk
    if RstxRBI = '0' then               -- asynchronous reset (active low)
      DataxDP     <= (others => '0');
      Data2xDP    <= (others => '0');
      Data3xDP    <= (others => '0');
      Data4xDP    <= (others => '0');
      RndCntxDP   <= 0;
      MsgLenxDP   <= (others => '0');
      StatexDP    <= init;
      FinBlockxSP <= '1';               --init to '1'
      JHFinalxSP  <= '0';
    elsif ClkxCI'event and ClkxCI = '1' then  -- rising clock edge
      DataxDP     <= DataxDN;
      Data2xDP    <= DataxDN(511 downto 0);
      Data3xDP    <= DataxDN(511 downto 0);
      Data4xDP    <= DataxDN(63 downto 0);
      RndCntxDP   <= RndCntxDN;
      MsgLenxDP   <= MsgLenxDN;
      StatexDP    <= StatexDN;
      FinBlockxSP <= FinBlockxSN;
      JHFinalxSP  <= JHFinalxSN;
    end if;
  end process p_clk;

-- the output
  DataOutxDO  <= DataxDP;               -- 1088 main output
  Data2OutxDO <= Data2xDP;              -- 512 bit replica 
  Data3OutxDO <= Data3xDP;              -- 512 bit replica 
  Data4OutxDO <= Data4xDP;              -- 64 bit replica 
  

  
end rtl;

Generated on Tue Nov 22 15:16:34 CET 2011
Home