Unable to synthesize code. GHDL throws an array bounds error

160 Views Asked by At

I'm new to Stack Overflow and to VHDL too. I have completed the logic of an N-bit shifter and tested it using a testbench. But am unable to synthesize it.

While synthesizing I get an error saying "left and right bounds of a slice must be either constant or dynamic" (it is in line 37 and 45, also visible in the attached picture). Can somebody please tell what I need to fix (and perhaps how)?

library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.numeric_std.ALL;
use work.types.all;
use work.functions.all;
use work.casts.all;

entity logbarrel is
    generic (   N     : natural := 32
          );
    port    (   a     : in  std_logic_vector(N-1       downto 0); -- input data word
                func  : in  std_logic_vector(  2       downto 0); -- ctrl word (000=>>, 001=<<, 010=*>, 011=<*, 100=>>>)
                shamt : in  std_logic_vector(log2(N)-1 downto 0); -- shift amount
                y     : out std_logic_vector(N-1       downto 0)  -- output data word
          );
end;

architecture rtl1 of logbarrel is
    begin
        process(all)
      constant stage : natural := log2(N);                              -- number of stages
      variable rotr  : arr_of_slv(stage-1 downto 0)(N-1 downto 0);      -- rotated words
      variable mask  : arr_of_slv(    N-1 downto 0)(N-1 downto 0);      -- masks for all possible shifts
      variable sh    : std_logic_vector(shamt'range) := (others =>'0'); -- used as actual shift amount
            
        begin
  
    --   left or right shift
            if to_int(func) = 1 OR to_int(func) = 3 then  --checking for left, easier
                sh := (others =>'0'); --left makes sh = 000
            else
                sh := (0 => '1', others =>'0'); --right makes sh = 001
            end if;
      
      --  1st stage
            if shamt(0) = '1' then   -- shift if needed
                rotr(stage-1) := a(N*(1-to_int(sh))+2*to_int(sh)-2 downto 0) & a(N-1 downto N*(1-to_int(sh))+2*to_int(sh)-2+1); --rotate
            else 
                rotr(stage-1) := a; --no shift
            end if; 
  
      -- i-th stage 
            for i in stage-2 downto 0 loop
                if shamt(stage-i-1) = '1' then    -- shift if needed
                    rotr(i) := rotr(i+1)(N*(1-to_int(sh))+(2*to_int(sh)-1)*2**(stage-i-1)-1 downto 0) & rotr(i+1)(N-1 downto N*(1-to_int(sh))+(2*to_int(sh)-1)*2**(stage-i-1)); --rotate
                else
                    rotr(i) := rotr(i+1); --no shift at this level
                end if; 
            end loop;
            
      -- mask the rotated data if needed
            for i in 0 to N-1 loop
                case func is
                    when "000" | "100"  => mask(i) := (N-1 downto N-1-i+1 => '0') & (N-i-1 downto 0 => '1'); -- right shift
                    when "001"          => mask(i) := (N-1 downto i => '1') & (i-1 downto 0 => '0'); -- left shift
                    when "010" | "011"  => mask(i) := (others => '1'); -- rotate
                    when others => mask(i) := (others => '0'); -- this case 101 should not occur
                end case; 
            end loop;   
      
      -- output masking
            y <= (N-1 downto N-to_int(shamt) => a(N-1)) & (rotr(0)(N-to_int(shamt)-1 downto 0) AND mask(to_int(shamt))(N-to_int(shamt)-1 downto 0)) when func = "100" else         -- masking for arith. right shift
                    rotr(0) AND mask(to_int(shamt));                          -- masking for all other cases
        end process;
    
  end;

Here's the original code skeleton, on which I had to change the lines only where TODO was written

library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.numeric_std.ALL;
use work.types.all;
use work.functions.all;
use work.casts.all;

entity logbarrel is
    generic (   N     : natural := 32
          );
    port    (   a     : in  std_logic_vector(N-1       downto 0); -- input data word
            func  : in  std_logic_vector(  2       downto 0); -- ctrl word (000=>>, 001=<<, 010=*>, 011=<*, 100=>>>)
                  shamt : in  std_logic_vector(log2(N)-1 downto 0); -- shift amount
            y     : out std_logic_vector(N-1       downto 0)  -- output data word
          );
end;

architecture rtl1 of logbarrel is
    begin
        process(all)
      constant stage : natural := log2(N);                              -- number of stages
      variable rotr  : arr_of_slv(stage-1 downto 0)(N-1 downto 0);      -- rotated words
      variable mask  : arr_of_slv(    N-1 downto 0)(N-1 downto 0);      -- masks for all possible shifts
            variable sh    : std_logic_vector(shamt'range) := (others =>'0'); -- used as actual shift amount
            
        begin
  
      -- left or right shift
            if TODO then  
                sh := TODO 
            else
                sh := TODO
            end if;
      
      --  1st stage
            if TODO then     -- shift if needed
                rotr(stage-1) := TODO
            else 
                rotr(stage-1) := TODO
            end if; 
  
      -- i-th stage 
            for i in TODO loop
                if TODO then    -- shift if needed
                    rotr(i) := TODO
                else
                    rotr(i) := TODO
                end if; 
            end loop;
            
      -- mask the rotated data if needed
            for i in 0 to N-1 loop
                case func is
                    when TODO   => mask(i) := TODO -- right shift
                    when TODO   => mask(i) := TODO -- left shift
                    when TODO   => mask(i) := TODO -- rotate
                    when others => mask(i) := TODO -- this case 101 should not occur
                end case; 
            end loop;   
      
      -- output masking
            y <=  TODO when TODO else         -- masking for arith. right shift
                        TODO                          -- masking for all other cases
        end process;
    
  end;

And here is the testbench used to test this as an instantiation. (It also initializes another such entity, I'll paste its code below, in case you want it).

library IEEE; 
use IEEE.std_logic_1164.all;
use IEEE.numeric_std.all;
use work.casts.all;
use work.functions.all;

entity shifter_tb is
  generic( N    : natural := 32;
           ainit: natural := 16#72345678#);
end;

architecture test of shifter_tb is
  signal a, y1, y2 : std_logic_vector(N-1 downto 0):= to_slv(ainit,N); 
  signal func      : std_logic_vector(  2 downto 0);
  signal shamt     : std_logic_vector(log2(N)-1 downto 0);
begin

  stimuli: process
  begin
   -- for i in 0 to 2**a'length-1 loop  
    --  a <= to_slv(i, a'length);     
      for j in 0 to 4 loop --2**func'length-1 loop 
        func <= to_slv(j, func'length);
        for k in 0 to 2**shamt'length-1 loop
          shamt <= to_slv(k, shamt'length);         
          wait for 10 ns;
          case func is
            when "000"  =>  assert (y1 = y2)
                            report strs(y1) & strs(y2)  &  " = " & 
                                   str(a)  & " >> "  & strs(to_int(shamt))  & str(func)  ;
            when "001"  =>  assert (y1 = y2)
                            report strs(y1) &  str(y2)  &  " = " & 
                                   str(a)  & " << "  & strs(to_int(shamt))  & str(func)  ;
            when "010"  =>  assert (y1 = y2)
                            report strs(y1) &  str(y2)  &  " = " & 
                                   str(a)  & " *> "  & strs(to_int(shamt))  & str(func)  ;  
            when "011"  =>  assert (y1 = y2)
                            report strs(y1) &  str(y2)  &  " = " & 
                                   str(a)  & " <* "  & strs(to_int(shamt))  & str(func)  ;  
            when others =>  assert (y1 = y2)
                            report strs(y1) &   str(y2)  &  " = " & 
                                   str(a)  & " >>> " & strs(to_int(shamt))  & str(func)  ;                          
          end case;
        end loop;
      end loop; 
    --end loop;      
    wait;
  end process; 

  shifter1_inst: entity work.shifter
               generic map (N => N)
               port    map (a, func, shamt, y1); 
  shifter2_inst: entity work.logbarrel
               generic map (N => N)
               port    map (a, func, shamt, y2);                      
                            
end;

The other entity called shifter (the golden model):

library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.numeric_std.ALL;
use work.types.all;
use work.functions.all;
use work.casts.all;

entity shifter is
    generic (   N     : natural := 32
          );
    port    (   a     : in  std_logic_vector(N-1       downto 0);
            func  : in  std_logic_vector(  2       downto 0);
                  shamt : in  std_logic_vector(log2(N)-1 downto 0); 
            y     : out std_logic_vector(N-1       downto 0)
          );
end;

architecture rtl of shifter is
begin
    process(all)
        variable rotr, rotl, ashr, lshr, lshl : arr_of_slv(N-1 downto 0)(N-1 downto 0); 
    begin
                
        lshr(0) := a; lshl(0) := a; ashr(0) := a; rotr(0) := a; rotl(0) := a;
        for i in 1 to N-1 loop
            lshr(i) := (i-1 downto 0 => '0')    & a(N-1 downto i);
            lshl(i) := a((N-1)-i downto 0)      &  (i-1 downto 0 => '0');   
            ashr(i) := (i-1 downto 0 => a(N-1)) & a(N-1 downto i); 
            rotr(i) := a(    i-1 downto 0)      & a(N-1 downto i); 
            rotl(i) := a((N-1)-i downto 0)      & a(N-1 downto N-i);
        end loop;   
        
        y <=    lshr(to_int(shamt)) when func = "000" else
                    lshl(to_int(shamt)) when func = "001" else
                    rotr(to_int(shamt)) when func = "010" else
                    rotl(to_int(shamt)) when func = "011" else
                    ashr(to_int(shamt));
    end process;

end;

And finally the header files (not sure what they're called in the VHDL world) that are being used in the testbench and the instantiated architectures:

types:

library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;

package types is
  constant width : integer := 32;
  subtype byte         is       natural range 7 downto 0;
  subtype logic        is       std_logic;
  subtype byteT        is       std_logic_vector(byte);
  subtype word         is       std_logic_vector(width-1 downto 0);
  subtype uword        is       unsigned(width-1 downto 0);
  subtype sword        is       signed  (width-1 downto 0);
  type arr_of_slv      is       array   (natural range <>) of std_logic_vector;
  type matrix          is       array   (natural range <>, natural range <>) of std_logic;
end;

package body types is

end;

functions:

library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
use work.casts.all;
use work.types.all;

package functions is
  function log2  (a                      : natural)                             return natural;
  function replicate(s                   : std_logic; n: integer)               return std_logic_vector;
  function decode(arg                    : std_logic_vector)                    return std_logic_vector;
  function mux(sel, x                    : std_logic_vector)                    return std_logic;
  function mux(sel : std_logic_vector; x : arr_of_slv)                          return std_logic_vector;
 -- function mux(sel : std_logic_vector; x : arr_of_slv (0 TO M-1)(N-1 downto 0)) return std_logic_vector is
  function reduce(Inputs                 : std_logic_vector )                   return std_logic_vector;
  --function reduction( Inputs : arr_of_slv )                         return std_logic_vector;
end;  
  
package body functions is

  function log2 (a: natural) return natural IS
    variable val : natural := a;
    variable log : natural := 0;
  begin
    for i in a downto 0 loop
      val := val / 2;
      if val > 0 then
        log := log + 1;
      end if;
    end loop;
    return log;
  end;

  function replicate(s: std_logic; n: integer) return std_logic_vector is
    variable r : std_logic_vector(n-1 downto 0);
  begin
    for i in 0 to n-1 loop
      r(i) := s;
    end loop;
    return r;
  end;

  function decode (arg : std_logic_vector) return std_logic_vector is
        variable res : std_logic_vector((2**arg'length)-1 downto 0);
    begin
        res(to_int(arg)) := '1';
        return res;
    end;

  function mux( sel, x : std_logic_vector ) return std_logic is  
  begin
     
    return x(to_int(sel));

  end;

  function mux( sel : std_logic_vector; x: arr_of_slv) return std_logic_vector is  
  begin

  --  assert Inputs'length <= 2 ** sel'length
  --    report "Inputs size: " & integer'image(Inputs'length) & " is too big for the select";
     
    return x(to_int(sel));

  end;

  -- function mux(sel : std_logic_vector; x : arr_of_slv (0 TO M-1)(N-1 downto 0)) return std_logic_vector is
  --   variable y : std_logic_vector(x(0)'length-1 downto 0);
  -- begin
  --     y := x(to_int(sel));  
  --   return y;
  -- end; 

  function reduce( Inputs : std_logic_vector ) return std_logic_vector is
    constant N   : integer := Inputs'length;
    variable inp : std_logic_vector(N-1 downto 0);
  begin
    inp := Inputs;
    if(N = 4) then
      return inp(1 downto 0) xor inp(3 downto 2);
    else
      return reduce(inp((N-1) downto N/2)) xor reduce(inp(((N/2)-1) downto 0));
    end if;
  end;

  -- function reduction( Inputs: arr_of_slv ) return std_logic_vector is
  --   constant N   : integer := Inputs'length;
  --   variable inp : arr_of_slv(N-1 downto 0, 12-1 downto 0);
  -- begin
  --   --return x"1234"; --Inputs(0);
  --   inp := Inputs;
  --   if N = 1 then 
  --      return inp(0); 
  --   elsif N > 1 then
  --      return reduction(inp(N-1 downto N/2)) xor reduction(inp(N/2-1 downto 0));
  --   end if;   
  -- end;    
end;  

casts:

library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;

package casts is
  function to_int(arg: std_logic_vector)       return natural;
  function to_sint(arg: std_logic_vector)      return natural;
  function to_int(arg: unsigned)               return natural;
  function to_int(arg: signed)                 return natural;
  function to_slv(arg: integer; bits: integer) return std_logic_vector;
  function to_slv(arg: unsigned)               return std_logic_vector;
  function to_slv(arg: signed)                 return std_logic_vector;
  function to_slv(arg: std_ulogic_vector)      return std_logic_vector;
  function to_sslv(arg: integer; bits: natural) return std_logic_vector;

  function str(s: std_ulogic_vector)           return string;
  function str(s: integer)                     return string;
  function strs(s: std_ulogic_vector)          return string;
  function strs(s: integer)                    return string;
  function strs(s: std_logic)                  return string;
  function str(s: std_logic)                   return character;
end;

package body casts is
  
  subtype logic is std_logic;
  type logic_vector is array (natural range <>) of std_logic;

  function to_int (arg: std_logic_vector) return natural IS
  begin
    return to_integer(unsigned(arg));
  end;

  function to_sint (arg: std_logic_vector) return natural IS
    variable x : signed(arg'range);
  begin
    x := signed(arg);
    return to_integer(x);
  end;

  function to_int (arg: unsigned) return natural IS
  begin
    return to_integer(arg);
  end;

  function to_int (arg: signed) return natural IS
  begin
    return to_integer(arg);
  end;

  function to_slv(arg: integer; bits: integer) return std_logic_vector is
  begin
      return std_logic_vector(to_unsigned(arg,bits));
  end;

  function to_sslv(arg: integer; bits: natural) return std_logic_vector is
  begin
      return std_logic_vector(to_signed(arg,bits));
  end;

  function to_slv(arg: unsigned) return std_logic_vector IS     
  begin     
    return std_logic_vector(arg);    
  end;

  function to_slv(arg: std_ulogic_vector) return std_logic_vector IS     
  begin     
    return to_stdlogicvector(arg);    
  end;
  
  function to_slv(arg: signed) return std_logic_vector IS     
  begin     
    return std_logic_vector(arg);    
  end;

  function chr2sl (ch: in character) return std_logic is
    begin
      case ch is
        when 'U' | 'u' => return 'U';
        when 'X' | 'x' => return 'X';
        when '0'       => return '0';
        when '1'       => return '1';
        when 'Z' | 'z' => return 'Z';
        when 'W' | 'w' => return 'W';
        when 'L' | 'l' => return 'L';
        when 'H' | 'h' => return 'H';
        when '-'       => return '-';
        when OTHERS    => assert false
                          report "Illegal Character found" & ch
                          severity error;
                          return 'U';
      end case;
    end;
    
    function str2sl (s: string) return std_logic_vector is
      variable vector: std_logic_vector(s'LEFT - 1 DOWNTO 0);
    begin
      for i in s'RANGE loop
        vector(i-1) := chr2sl(s(i));
      end loop;
      return vector;
    end;

    function to_char(s: std_ulogic) return character is
    begin
      case s is
        when 'X' => return 'X';  
        when '0' => return '0';  
        when '1' => return '1';  
        when 'Z' => return 'Z';  
        when 'U' => return 'U';  
        when 'W' => return 'W';  
        when 'L' => return 'L';  
        when 'H' => return 'H';  
        when '-' => return '-';  
      end case;
    end;

  function str(s: std_ulogic_vector) return string is
    variable ret:string(1 to s'length);
    variable K  : integer:= 1;
  begin
    for J in s'range loop
      ret(K) := to_char(s(J));
      K := K + 1;
    end loop;
    return ret;      
  end;  

  function strs(s: std_ulogic_vector) return string is
  begin
    return str(s) & ' ';
  end;   

  function str(s: std_logic) return character is
  begin  
    return to_char(s);    
  end; 
  
  function strs(s: std_logic) return string is
  begin
    return str(s) & ' ';
  end; 

  function to_nstring(s: natural) return string is
    variable ret, iret : string(1 to 16);
    variable k, j      : integer;
    variable s1, s2, s3: natural := 0;
  begin  

    s1     := s;
    ret(1) := '0';  
    k      := 1;  
  
    while (s1 > 0 and K < 16) loop
      s2 := s1 / 10;
      s3 := s1 - (s2 * 10);
      if (s3 = 0) then 
        ret(k) := '0';
      elsif (s3 = 1) then
        ret(k) := '1';
      elsif (s3 = 2) then
        ret(k) := '2';
      elsif (s3 = 3) then
        ret(k) := '3';
      elsif (s3 = 4) then
        ret(k) := '4';
      elsif (s3 = 5) then
        ret(k) := '5';
      elsif (s3 = 6) then
        ret(k) := '6';
      elsif (s3 = 7) then
        ret(k) := '7';
      elsif (s3 = 8) then
        ret(k) := '8';
      elsif (s3 = 9) then
        ret(k) := '9';
      end if;
      k := k + 1;
      s1 := s2;
    end loop;
  
    if (k > 1) then
      k := k-1;
    end if;

    J := 1;
    while (k > 0) loop
      iret(j) := ret(k);
      k := k-1;
      j := j+1;
    end loop;        

    return iret;      

  end;


  function str(s: integer) return string is
  begin
    if (s < 0) then
      return "-" & to_nstring(-s);
    else
      return to_nstring(s);
    end if;    
  end;
 
  function strs(s: integer) return string is
  begin
    return str(s) & ' ';
  end;

end;
0

There are 0 best solutions below