------------------------------------------------------------
-- Copyright: 2011 George Mason University, Virginia USA
--            http://www.iis.ee.ethz.ch/~sha3
------------------------------------------------------------
-------------------------------------------------------------------------------
-- Title      : Modified version of the simulstuff
-- Project    : Shabziger
-------------------------------------------------------------------------------
-- File       : simulstuff.vhd
-- Author     : Frank K. Guerkaynak  
-- Company    : Integrated Systems Laboratory, ETH Zurich
-- Created    : 2011-08-22
-- Last update: 2011-08-22
-- Platform   : ModelSim (simulation), Synopsys (synthesis)
-- Standard   : VHDL'87
-------------------------------------------------------------------------------
-- Description: This is a branch from the original simulstuff by H. Kaeslin et
--              al. It was slightly modified for Acacia. In the Shabziger
--              project we have modified that it does not use an output file
--              A single file is used to read in the stimuli
-------------------------------------------------------------------------------
-- Copyright (c) 2011 Integrated Systems Laboratory, ETH Zurich
-------------------------------------------------------------------------------
-- Revisions  :
-- Date        Version  Author  Description
-- 2011-08-22  1.0      kgf	    Created
-- 2011-09-01  1.0      kgf	    Copied even more from Peter Luethis simulstuff u5
-------------------------------------------------------------------------------
-------------------------------------------------------------------------------
use std.textio.all;
library ieee;
use ieee.std_logic_textio.all;   -- read and write overloaded for std_logic
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
use ieee.math_real.Uniform;      -- IEEE 1076.2 real math package
use ieee.math_real.Trunc;
-------------------------------------------------------------------------------
-- package declaration
package simulstuff is
-- kgf's silly vector 2 hex conversion.
   procedure four2hex
     (p_line: inout line;
      value : in std_logic_vector( 3 downto 0));
   
   procedure  vector2hex
     (p_line: inout line;
      vector : in std_logic_vector);
  
   -- support for file handling
   function FileOpenMessage
      (filename : string; status : file_open_status)
      return string;
   procedure GetFileEntry
      (fileentry : inout std_logic_vector;
       in_line, in_line_tmp : inout line; filename : string);
   procedure GetFileEntry
      (fileentry : inout std_logic;
       in_line, in_line_tmp : inout line; filename : string);
  -- signed/unsigned integer => signed
  procedure GetFileEntryInt2x
    (val                  : inout signed;
     in_line, in_line_tmp : inout line; filename : string);
  -- signed/unsigned integer => (signed) std_logic_vector
  procedure GetFileEntryInt2x
    (val                  : inout std_logic_vector;
     in_line, in_line_tmp : inout line; filename : string);
  -- unsigned integer => unsigned
  procedure GetFileEntryUInt2x (
    val                  : inout unsigned;
    in_line, in_line_tmp : inout line; filename : string);
  -- unsigned integer => (unsigned) std_logic_vector
  procedure GetFileEntryUInt2x (
    val                  : inout std_logic_vector;
    in_line, in_line_tmp : inout line; filename : string);
  -- signed/unsigned integer => signed
  procedure GetFileEntryInt
    (val                  : inout integer;
     in_line, in_line_tmp : inout line; filename : string);
   function FileReadMessage
      (filename : string; read_ok : boolean; lineread : string)
      return string;
   -- support for process coordination, patterned after a traffic light
   type trafficlight is (
      orange,   -- simulation run is waiting to start
      green,    -- simulation run is under way
      green2,   -- idem but there are no expected responses left
      yellow,   -- simulation run has exhausted its stimuli
      red );    -- simulation run has completed
   type trafficlightvector is array (natural range <>) of trafficlight;
   function ResolveTrafficLight
      (argument : in trafficlightvector) return trafficlight;   
   -- support for evaluating responses from the MUT
   type respmatchtype is (
      mok,   -- o.k. = both logic value and drive strength do match
      mlf,   -- logic fail = logic value or tristate status does not match
      msf,   -- strength fail = weak instead of strong drive or viceversa
      mil ); -- illegal response = actual response has value "don't care"
   type vectorwise_matchtable
      is array (respmatchtype, respmatchtype) of respmatchtype;
   constant check_vectorwise : vectorwise_matchtable := (
      --     ----------------------------------
      --     | mok  mlf  msf  mil       |     |   
      --     ----------------------------------
             ( mok, mlf, msf, mil ), -- | mok |
             ( mlf, mlf, mlf, mil ), -- | mlf |
             ( msf, mlf, msf, mil ), -- | msf |
             ( mil, mlf, mil, mil )  -- | mil |
             );   -- symmetric, dimensions may be interchanged
   type respaccounttype is record
      numberof_mch,  -- number of responses checked so far
      numberof_mok,  -- see above for this and all other fields
      numberof_mlf,
      numberof_msf,
      numberof_mil : natural;
   end record;
   procedure CheckResponse
      (actresp, expresp : in std_logic_vector;
       respmatch : out respmatchtype;
       respaccount : inout respaccounttype);
   procedure CheckResponse
      (actresp, expresp : in std_logic;
       respmatch : out respmatchtype;
       respaccount : inout respaccounttype);   
   function AnnotateFailureMessage
      (respmatch : in respmatchtype) return string;
   procedure PutSimulationReportSummary
      (respaccount : in respaccounttype);
   -- support for generation of random test patterns
   procedure GenerateRandomVector
      (randvectwidth : in natural;
       statevar1, statevar2 : inout integer;
       randvect : out std_logic_vector);   -- unconstrained array type
  procedure GenerateRandomBit
    (probability_of_1     : in    real;
     statevar1, statevar2 : inout integer;
     randbit              : out   std_logic);
  procedure GenerateRandomInteger
    (min, max             : in    integer;
     statevar1, statevar2 : inout integer;
     randinteger          : out   integer);
end package simulstuff;
--=============================================================================
-- package body
package body simulstuff is
   procedure four2hex
     (p_line: inout line;
      value : in std_logic_vector( 3 downto 0))
     is
   begin  
      case value is
        when "0000" => write (p_line, string'("0")); 
        when "0001" => write (p_line, string'("1")); 
        when "0010" => write (p_line, string'("2")); 
        when "0011" => write (p_line, string'("3")); 
        when "0100" => write (p_line, string'("4")); 
        when "0101" => write (p_line, string'("5")); 
        when "0110" => write (p_line, string'("6")); 
        when "0111" => write (p_line, string'("7")); 
        when "1000" => write (p_line, string'("8")); 
        when "1001" => write (p_line, string'("9")); 
        when "1010" => write (p_line, string'("a")); 
        when "1011" => write (p_line, string'("b")); 
        when "1100" => write (p_line, string'("c")); 
        when "1101" => write (p_line, string'("d")); 
        when "1110" => write (p_line, string'("e")); 
        when "1111" => write (p_line, string'("f")); 
        when others => write (p_line, string'("X"));
      end case;
   end procedure four2hex;
  
   procedure  vector2hex
     (p_line: inout line;
      vector : in std_logic_vector)
   is
     variable a : std_logic_vector( vector'length-1 downto 0 ):= vector ;
     variable i : natural;
     variable steps : natural; 
     variable b : std_logic_vector( 3 downto 0);
     variable extra_bits : boolean;
   begin
     extra_bits := true;
     b := "0000";
     i := a'length;
     
     if (i mod 4 = 1) then
       b := "000" & a (i-1);
       i := i-1 ;
     elsif (i mod 4 = 2) then
       b := "00" & a(i-1 downto i-2); 
       i := i-2;
     elsif (i mod 4 = 3) then
       b := '0' & a(i-1 downto i-3);
       i := i-3;
     else
       extra_bits := false;
     end if; 
    if extra_bits then
      four2hex(p_line,b);
    end if;
     
    steps := (i / 4) - 1;
    for j in 0 to steps loop
      b:= a ( (steps-j)*4+3 downto (steps-j)*4);
      four2hex(p_line,b);
    end loop; 
   end vector2hex;
  
   -- purpose: translate file open status into a human-readable text string.
   function FileOpenMessage (filename : string; status : file_open_status)
      return string is
   begin
      case status is
         when open_ok => return "File "& filename &" opened successfully.";
         when status_error => return "File "& filename &" already opened.";
         when name_error => return
            "File "& filename &" does not exist or can not be created.";
         when mode_error => return
            "File "& filename &" can not be opened in write or append mode.";
      end case;
   end FileOpenMessage;
   -- purpose: get one entry from the stimuli or expected responses file.
   procedure GetFileEntry
      (fileentry : inout std_logic_vector;
       in_line, in_line_tmp : inout line;
       filename : string)
   is
      variable read_ok : boolean;
   begin
      -- extract next entry to obtain the value of formal variable fileentry
      read(in_line,fileentry,read_ok);
      if not read_ok then
         report FileReadMessage(filename,read_ok,in_line_tmp.all)
            severity error;
      end if;
   end GetFileEntry;
   -- purpose: above procedure overloaded for scalars rather than vectors.
   procedure GetFileEntry
      (fileentry : inout std_logic;
       in_line, in_line_tmp : inout line; filename : string)
   is
      variable read_ok : boolean;
   begin
      -- extract next entry to obtain the value of formal variable fileentry
      read(in_line,fileentry,read_ok);
      if not read_ok then
         report FileReadMessage(filename,read_ok,in_line_tmp.all)
            severity error;
      end if;
   end GetFileEntry;
  -- ### signed/unsigned integer => signed
  -- purpose: get one entry from the stimuli or expected responses file
  -- source (file entry) : signed/unsigned integer
  -- target (VHDL signal): signed
  procedure GetFileEntryInt2x
    (val                  : inout signed;
     in_line, in_line_tmp : inout line;
     filename             :       string)
  is
    variable read_ok   : boolean;
    variable fileentry : integer;
  begin
    -- extract next entry to obtain the value of formal variable fileentry
    read(in_line, fileentry, read_ok);
    if not read_ok then
      report FileReadMessage(filename, read_ok, in_line_tmp.all)
        severity error;
    end if;
    val := to_signed(fileentry, val'length);
  end GetFileEntryInt2x;
  -- ### signed/unsigned integer => std_logic_vector
  -- purpose: get one entry from the stimuli or expected responses file
  -- source (file entry) : signed/unsigned integer
  -- target (VHDL signal): (signed) std_logic_vector
  procedure GetFileEntryInt2x
    (val                  : inout std_logic_vector;
     in_line, in_line_tmp : inout line;
     filename             :       string)
  is
    variable tmp_signed : signed(1 to val'length);
  begin
    -- use overloaded procedure
    GetFileEntryInt2x(tmp_signed, in_line, in_line_tmp, filename);
    val := std_logic_vector(tmp_signed);
  end GetFileEntryInt2x;
  -- ### unsigned integer => unsigned
  -- purpose: get one entry from the stimuli or expected responses file
  -- source (file entry) : unsigned integer
  -- target (VHDL signal): unsigned
  procedure GetFileEntryUInt2x (
    val                  : inout unsigned;
    in_line, in_line_tmp : inout line;
    filename             :       string)
  is
    variable read_ok   : boolean;
    variable fileentry : integer;
  begin
    -- extract next entry to obtain the value of formal variable fileentry
    read(in_line, fileentry, read_ok);
    if not read_ok then
      report FileReadMessage(filename, read_ok, in_line_tmp.all) severity error;
    end if;
    val := to_unsigned(fileentry, val'length);
  end GetFileEntryUInt2x;
  -- ### unsigned integer => (unsigned) std_logic_vector
  -- purpose: get one entry from the stimuli or expected responses file
  -- source (file entry) : unsigned integer
  -- target (VHDL signal): (unsigned) std_logic_vector
  procedure GetFileEntryUInt2x (
    val                  : inout std_logic_vector;
    in_line, in_line_tmp : inout line;
    filename             :       string)
  is
    variable tmp_unsigned : unsigned(1 to val'length);
  begin
    -- use overloaded procedure
    GetFileEntryUInt2x(tmp_unsigned, in_line, in_line_tmp, filename);
    val := std_logic_vector(tmp_unsigned);
  end GetFileEntryUInt2x;
  -- ### unsigned integer => unsigned
  -- purpose: get one entry from the stimuli or expected responses file
  -- source (file entry) : unsigned integer
  -- target (VHDL signal): unsigned
  procedure GetFileEntryInt (
    val                  : inout integer;
    in_line, in_line_tmp : inout line;
    filename             :       string)
  is
    variable read_ok   : boolean;
  begin
    -- extract next entry to obtain the value of formal variable fileentry
    read(in_line, val, read_ok);
    if not read_ok then
      report FileReadMessage(filename, read_ok, in_line_tmp.all) severity error;
    end if;
  end GetFileEntryInt;
  -----------------------------------------------------------------------------
  -- purpose: overload write method to accept also unsigned
  procedure write (outline : inout line; val : in unsigned) is
  begin
    write(outline, std_logic_vector(val));
  end write;
  -- purpose: overload write method to accept also signed
  procedure write (outline : inout line; val : in signed) is
  begin
    write(outline, std_logic_vector(val));
  end write;
  -----------------------------------------------------------------------------
   -- purpose: translate file read status into a human-readable text string.
   function FileReadMessage
      (filename : string;
       read_ok : boolean; lineread : string)
      return string is
   begin
      if read_ok=true then
         return "Line `"& lineread &"' sucessfully read from file "
            & filename &".";
      else
         return "Missing or unsuitable entry found while reading line `"
            & lineread &"' from file "& filename &".";
      end if;
   end FileReadMessage;
-------------------------------------------------------------------------------
   -- purpose: determine actual status of simulation run,
   --    argument simply overwrites previous signal value
   --    as simulation progress never moves back.
   function ResolveTrafficLight
      (argument : in trafficlightvector) return trafficlight
   is
      type trafficlighttable is array (trafficlight, trafficlight)
         of trafficlight;
      constant colortable : trafficlighttable := (
      --     --------------------------------------------------
      --     |  orange   green    green2   yellow   red       |        |
      --     --------------------------------------------------
             ( orange,   green,   green2,  yellow,  red ), -- | orange |
             ( green,    green,   green2,  yellow,  red ), -- | green  |
             ( green2,   green2,  green2,  yellow,  red ), -- | green2 |
             ( yellow,   yellow,  yellow,  yellow,  red ), -- | yellow |
             ( red,      red,     red,     red,     red )  -- | red    |
             );   -- commutative, dimensions may be interchanged
      variable result: trafficlight := orange;
   begin
      for i in argument'range loop
         result := colortable(result,argument(i));
      end loop;
      return result;
   end ResolveTrafficLight;
-------------------------------------------------------------------------------
   -- purpose: check to what extent actual and expected responses match,
   --    return a grade, and update failure account record accordingly.
   procedure CheckResponse
      (actresp, expresp : in std_logic_vector;
       respmatch : out respmatchtype;
       respaccount : inout respaccounttype)
   is
      type bitwise_matchtable is array (std_logic, std_logic) of respmatchtype;
      constant check_bitwise : bitwise_matchtable := (
      --     ---------------------------------------------------------
      -- exp |  U    X    0    1    Z    W    L    H    -        |act|  
      --     ---------------------------------------------------------
             ( mok, mlf, mlf, mlf, mlf, mlf, mlf, mlf, mok ), -- | U |
             ( mlf, mok, mlf, mlf, mlf, msf, mlf, mlf, mok ), -- | X |
             ( mlf, mlf, mok, mlf, mlf, mlf, msf, mlf, mok ), -- | 0 |
             ( mlf, mlf, mlf, mok, mlf, mlf, mlf, msf, mok ), -- | 1 |
             ( mlf, mlf, mlf, mlf, mok, mlf, mlf, mlf, mok ), -- | Z |
             ( mlf, msf, mlf, mlf, mlf, mok, mlf, mlf, mok ), -- | W |
             ( mlf, mlf, msf, mlf, mlf, mlf, mok, mlf, mok ), -- | L |
             ( mlf, mlf, mlf, msf, mlf, mlf, mlf, mok, mok ), -- | H |
             ( mil, mil, mil, mil, mil, mil, mil, mil, mil )  -- | - |
             );   -- act is the 1st and exp the 2nd dimension
      variable bitwise_match, vectorwise_match : respmatchtype := mok;     
   begin
      assert expresp'length=actresp'length and expresp'length>0
         report " Cardinality of response does not match or is zero."
         severity warning;
      for i in expresp'range loop
         bitwise_match := check_bitwise(actresp(i),expresp(i));
         vectorwise_match := check_vectorwise(vectorwise_match,bitwise_match);
      end loop;
      respmatch := vectorwise_match;
      case vectorwise_match is
         when mok => respaccount.numberof_mok := respaccount.numberof_mok +1;
         when mlf => respaccount.numberof_mlf := respaccount.numberof_mlf +1;
         when msf => respaccount.numberof_msf := respaccount.numberof_msf +1;
         when mil => respaccount.numberof_mil := respaccount.numberof_mil +1;
      end case;
      respaccount.numberof_mch := respaccount.numberof_mch +1;
   end CheckResponse;
   -- purpose: above procedure overloaded for scalars rather than vectors.
   procedure CheckResponse
      (actresp, expresp : in std_logic;
       respmatch : out respmatchtype;
       respaccount : inout respaccounttype)
   is
      variable actrespvector, exprespvector : std_logic_vector(0 to 0);    
   begin
      actrespvector(0) := actresp; exprespvector(0) := expresp;
      CheckResponse(actrespvector,exprespvector,respmatch,respaccount);
   end CheckResponse;
-------------------------------------------------------------------------------
   -- purpose: generate a text string that comments on how a response matches.
   function AnnotateFailureMessage (respmatch : in respmatchtype)
      return string is
   begin
      case respmatch is
         when mok => return string'     -- everything as expected
            ("^^ matched.            ");
         when mlf => return string'     -- wrong logic state or yes/no drive
            ("^^ failed logically!   ");
         when msf => return string'     -- wrong drive strength 
            ("^^ failed in strength! ");
         when others => return string'  -- no legal logic value for simulation
            ("^^ failed illegally!   ");
     end case;                         
   end AnnotateFailureMessage;
-------------------------------------------------------------------------------
   -- purpose: summarize simulation report and write it to report file.
   procedure PutSimulationReportSummary
      (respaccount : in respaccounttype)
   is
      variable out_line : line;
      
   begin
      -- separator
      write(out_line,string'("% ======== Simulation Report Summary ========"));
      writeline(output,out_line);
      -- 1st line
      write(out_line,string'("% A total of "));
      write(out_line,respaccount.numberof_mch);
      write(out_line,string'(" responses have been checked, out of which "));
      write(out_line,respaccount.numberof_mok);
      write(out_line,string'(" matched expectations."));       
      writeline(output,out_line); -- to screen ?? 
      -- 2nd line
      assert respaccount.numberof_mch /= respaccount.numberof_mok
         report "All Results Match! " severity note;
      assert respaccount.numberof_mch = respaccount.numberof_mok
         report "ERRORS in Simulation" severity warning;
   end PutSimulationReportSummary;
-------------------------------------------------------------------------------
   -- purpose: generate binary random vectors of parametrized word width that 
   --    should be uniformly distributed over interval [0,2**randvectwidth-1].
   -- limitation: mantissa of VHDL type reals has 23bits, so randvectwidth 
   --    must not exceed this value as outcome is otherwise uncertain.
   -- note: state variables of procedure Uniform must be kept within the 
   --    calling process because variables in a subprogram do not persist.
   -- findings: repeated calls of procedure ieee.math_real.Uniform with
   --    identical seeds indeed result in identical pseudo random numbers.
   procedure GenerateRandomVector
      (randvectwidth : in natural;
       statevar1, statevar2 : inout integer;
       randvect : out std_logic_vector)   -- unconstrained array type
   is
      constant upperbound : real := (2.0**randvectwidth)-1.0;
      variable randreal01 : real := 0.0;
      variable randscaled, randtruncd : real := 0.0;
      variable randinteger : integer := 0;
   begin
      -- obtain a random real in [0,1]
      Uniform(statevar1,statevar2,randreal01);
      -- rescale interval [0,1] to [0,upperbound]
      randscaled := randreal01*(upperbound+1.0);
      -- truncate to next smaller integer (still of type real, though)
      if randscaled/=(upperbound+1.0) then -- almost always
         randtruncd := Trunc(randscaled);
      else -- avoid spillover when randreal01 was exactly 1.0
         randtruncd := 0.0; -- 0.0 or upperbound is largely immaterial 
      end if;
      -- convert to a binary vector
      randinteger := integer(randtruncd);
      randvect := std_logic_vector(
         to_unsigned(randinteger,randvectwidth));
   end GenerateRandomVector;
 -- purpose: generate a random bit with some given probability of being '1'.
  -- note: state variables of procedure Uniform must be kept within the 
  --    calling process because variables in a subprogram do not persist.
  -- findings: repeated calls of procedure ieee.math_real.Uniform with
  --    identical seeds indeed result in identical pseudo random numbers.
  procedure GenerateRandomBit
    (probability_of_1     : in    real;
     statevar1, statevar2 : inout integer;
     randbit              : out   std_logic) 
  is
    variable randreal01 : real := 0.0;
  begin
    -- obtain a random real in the open interval ]0,1[
    Uniform(statevar1, statevar2, randreal01);
    -- set randbit according to threshold
    if (probability_of_1 > randreal01) then
      randbit := '1';
    else
      randbit := '0';
    end if;
  end GenerateRandomBit;
  -- purpose: generate random integer in the range [min, max], both included.
  -- note: state variables of procedure Uniform must be kept within the 
  --    calling process because variables in a subprogram do not persist.
  -- findings: repeated calls of procedure ieee.math_real.Uniform with
  --    identical seeds indeed result in identical pseudo random numbers.
  procedure GenerateRandomInteger
    (min, max             : in    integer;
     statevar1, statevar2 : inout integer;
     randinteger          : out   integer)  
  is
    variable randreal01  : real := 0.0;
    constant SPREADBOUND : real := real(max-min+1);
    variable randscaled  : real := 0.0;
  begin
    -- obtain a random real in the open interval ]0,1[
    Uniform(statevar1, statevar2, randreal01);
    -- scale open interval ]0,1[ to open interval ]0,SPREADBOUND[
    randscaled  := randreal01*SPREADBOUND;
    -- truncate to next smaller integer in the closed interval [0,max-min] and
    -- add the mininum value to get an integer in the closed interval [min,max]
    randinteger := integer(Trunc(randscaled)) + min;
  end GenerateRandomInteger;
-------------------------------------------------------------------------------
end package body simulstuff;