Feed

Enter your email address:

Delivered by FeedBurner

Tuesday, April 16, 2013

Finite state machine -pattern checker in vhdl

When a certain serial binary communication
channel is operating correctly, all blocks of 0's are
of even length and all blocks of 1's are of odd
length. The machine should produce and output
pulse z = 1 whenever discrepancy from the above
pattern is detected.
Example:
X : 0 0 1 0 0 0 1 1 1 0 1 1 0 0…
Z : 0 0 0 0 0 0 1 0 0 0 1 0 1 0…



library ieee;
use ieee.std_logic_1164.all;

entity fsm_prob3 is
 
  port (
    clk                : in  std_logic;
    rst_a              : in  std_logic;
    ip                 : in  std_logic;
    op                 : out std_logic);

end fsm_prob3;

architecture fsm_arch of fsm_prob3 is

  type state_t is (s_idle,s1 ,s2, s3);
  signal present_state : state_t;
  signal next_state : state_t;
 
begin  -- fsm_arch

p1: process (present_state,ip)
begin  -- process p1

  case present_state is

  when s_idle =>
    if ip='1' then
      op <= '0';
      next_state <= s1;
      else
        op <= '0';
        next_state <= s2;
    end if;

  when s1 =>
    if ip = '1' then
      op <= '0';
      next_state <= s3;
      else
        op<='0';
        next_state <= s2;
    end if;

  when s2 =>
    if ip = '1' then
      op <= '1';
      next_state <= s1;
      else
        op <= '0';
        next_state <= s_idle;
    end if;

  when s3 =>
    if ip = '1' then
      op <= '0';
      next_state <= s1;
      else
        op <= '1';
        next_state <= s2;
    end if; 
  end case;
end process p1;

seq_p: process (clk, rst_a)
begin  -- process seq_p
  if rst_a = '1' then                   -- asynchronous reset (active high)
   
    present_state <= s_idle;
  elsif clk'event and clk = '1' then    -- rising clock edge
   
    present_state <= next_state;
  end if;
end process seq_p;
 

end fsm_arch;

User defined package in vhdl example

library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_arith.all;

package combo_logic is

  function mux2x1 (d1,d2,sel : std_logic) return std_logic;
  function parity_chk (signal d_in : std_logic_vector) return std_logic;
  function left_shift (signal d_in : std_logic_vector; signal shift_by : integer)  return bit_vector;
  function right_shift (signal d_in : std_logic_vector; signal shift_by : integer) return bit_vector; 
 
end combo_logic;


package body combo_logic is
--------------------------------------------------------------------------------
--function body for mux2x1
-------------------------------------------------------------------------------
 function mux2x1 (d1,d2,sel : std_logic) return std_logic
   is begin

        if(sel='0')then

        return d1;

        else

        return d2;
     end if;
 end mux2x1;
 ------------------------------------------------------------------------------
 --function body for parity_chk
 ------------------------------------------------------------------------------

 function parity_chk (signal d_in : std_logic_vector) return std_logic
   is
   constant len : integer:=(d_in)'length-1;
   variable tmp : std_logic:='0';
 begin
   for i in len loop
     tmp:=tmp xor d_in(i);
   end loop;  -- i
  
 return tmp;
 end function;
-------------------------------------------------------------------------------
--function body for left_shift
-------------------------------------------------------------------------------

 function left_shift (signal d_in : std_logic_vector; signal shift_by : integer)  return bit_vector
   is
   constant len : integer:=d_in'length;
   variable tmp : bit_vector(len-1 downto 0):=to_bitvector(d_in);
  
 begin
  assert len>shift_by report "shift_by greater than length of input data" severity error;
  tmp:=tmp rol shift_by;
  return tmp;
 end function;
-------------------------------------------------------------------------------
--function body for right_shift
-------------------------------------------------------------------------------

 function right_shift (signal d_in : std_logic_vector; signal shift_by : integer)  return bit_vector
   is
   constant len : integer:=d_in'length;
   variable tmp : bit_vector(len-1 downto 0):=to_bitvector(d_in);
 begin
   assert len>shift_by report "shift_by greater than length of input data" severity error;
  tmp:=tmp ror shift_by;
  return tmp;
 end function;

end combo_logic;

Tuesday, April 9, 2013

4 bit full adder verilog code


module full_adder_4b(sum,cout,a,b,cin);
   output [3:0] sum;
   output     cout;
   input [3:0]     a,b;
   input     cin;

   full_adder f1 (sum[0], cout0, a[0], b[0], cin);
   full_adder f2 (sum[1], cout1, a[1], b[1], cout0);
   full_adder f3 (sum[2], cout2, a[2], b[2], cout1);
   full_adder f4 (sum[3], cout, a[3], b[3], cout2);

   endmodule

D latch verilog code


module d_latch(q, q_bar, d_in, enb);

   output q,q_bar;
   input  d_in;
   input  enb;

   nand g1 (s, d_in, enb),
        g2 (r, d_bar, enb);
  
   not g3 (d_bar,d_in);
   nand g4 (q, s, q_bar);
   nand g5 (q_bar, r, q);

   endmodule
  

4:16 decoder verilog code

module decoder_4x16 (d_out, d_in);
   output [15:0] d_out;
   input [3:0]      d_in;
   parameter tmp = 16'b0000_0000_0000_0001;
  


assign d_out = (d_in == 4'b0000) ? tmp   :
               (d_in == 4'b0001) ? tmp<<1:
               (d_in == 4'b0010) ? tmp<<2:
           (d_in == 4'b0011) ? tmp<<3:
           (d_in == 4'b0100) ? tmp<<4:
           (d_in == 4'b0101) ? tmp<<5:
           (d_in == 4'b0110) ? tmp<<6:
           (d_in == 4'b0111) ? tmp<<7:
           (d_in == 4'b1000) ? tmp<<8:
           (d_in == 4'b1001) ? tmp<<9:
           (d_in == 4'b1010) ? tmp<<10:
           (d_in == 4'b1011) ? tmp<<11:
           (d_in == 4'b1100) ? tmp<<12:
           (d_in == 4'b1101) ? tmp<<13:
           (d_in == 4'b1110) ? tmp<<14:
           (d_in == 4'b1111) ? tmp<<15: 16'bxxxx_xxxx_xxxx_xxxx;
            
              
             endmodule

Priority encoder verilog code

module prio_enco_8x3(d_out, d_in);

   output [2:0] d_out;
   input [7:0] d_in ;


assign d_out = (d_in[7] ==1'b1 ) ? 3'b111:
               (d_in[6] ==1'b1 ) ? 3'b110:
               (d_in[5] ==1'b1 ) ? 3'b101:
                 (d_in[4] ==1'b1) ? 3'b100:
                 (d_in[3] ==1'b1) ? 3'b011:
                 (d_in[2] ==1'b1) ? 3'b010:
                 (d_in[1] ==1'b1) ? 3'b001: 3'b000;

   endmodule

Friday, April 5, 2013

Parity generator structural vhdl code

library IEEE;
use IEEE.std_logic_1164.all;
use IEEE.std_logic_arith.all;
use IEEE.std_logic_unsigned.all;

entity parity_gen is
 
  port (
    clk       : in  std_logic;
    rst_a     : in  std_logic;
    valid_in  : in  std_logic;
    d_in      : in  std_logic;          -- input serial data stream
    valid_out : out std_logic;
    parity    : out std_logic;
    data_o    : out std_logic_vector (7 downto 0));

end parity_gen;

architecture parity_gen_arch of parity_gen is

  component d_ff is
 
  port (
     rst  : in  std_logic;               -- asynchronous reset
     clk  : in  std_logic;               -- clock
     en   : in  std_logic;               -- control signal 
     d_in : in  std_logic;               -- input data
     q    : out std_logic                -- output data
    );           

  end component;
 
  function parity_gen_func (par : in std_logic_vector (7 downto 0)) return std_logic is
  begin
  return par(0)xor par(1)xor par(2)xor par(3)xor par(4)xor par(5)xor par(6)xor par(7);
  end parity_gen_func;

  signal count : std_logic_vector (2 downto 0) := "000";
  signal temp : std_logic_vector (7 downto 0);

begin  -- parity_gen_arch

   d_ff1: d_ff port map (rst_a, clk, valid_in, d_in, temp(0));
   d_ff2: d_ff port map (rst_a, clk, valid_in, temp(0), temp(1));
   d_ff3: d_ff port map (rst_a, clk, valid_in, temp(1), temp(2));
   d_ff4: d_ff port map (rst_a, clk, valid_in, temp(2), temp(3));
   d_ff5: d_ff port map (rst_a, clk, valid_in, temp(3), temp(4));
   d_ff6: d_ff port map (rst_a, clk, valid_in, temp(4), temp(5));
   d_ff7: d_ff port map (rst_a, clk, valid_in, temp(5), temp(6));
   d_ff8: d_ff port map (rst_a, clk, valid_in, temp(6), temp(7));
  
data_o<= temp;
parity <= parity_gen_func(temp);
  
p1:   process (clk, rst_a)
        begin       
    if rst_a = '1' then                 -- asynchronous reset
      valid_out <= '0';
     
    elsif clk'event and clk ='1' then
    if valid_in = '1' then
        count<= count + '1';   
    end if; 
    if count = "111" then
        valid_out <= '1';
    else
        valid_out <= '0';
    end if;
    end if;
  end process p1;
 
end parity_gen_arch;

Barrel shifter with multi cycle and textio vhdl code

library IEEE;
use IEEE.std_logic_1164.all;
use IEEE.std_logic_arith.all;
use IEEE.std_logic_unsigned.all;

entity barrel_shifter_multi is
 
  port (
    d_in          : in bit_vector (7 downto 0);
    clk, rst_a    : in bit;
    shift_lt_rt   : in bit;                     --0=>left shift , 1=> right shift
    shift_by      : in bit_vector (2 downto 0); -- 000=>parallel load, other=> shift amount
    d_out      : out bit_vector (7 downto 0)
    );

end barrel_shifter_multi;

architecture arch of barrel_shifter_multi is
signal temp_a,temp_b,temp_c           : bit_vector (7 downto 0);     --signal to pass input
signal temp_sl1,temp_sl3,temp_sl2     : bit;                         --signal to pass shift_lt_rt value
signal temp_sby1,temp_sby2,temp_sby3  : bit_vector (2 downto 0);     --signal to pass shift_by value
signal temp_4,temp_2, temp_1          : bit_vector (7 downto 0);     --signal to pass output
begin  -- arch

  d_1: process (clk,rst_a)
  begin  -- process
    if rst_a = '1' then                   -- asynchronous reset (active high)
      temp_a <= "00000000";
    elsif clk'event and clk = '1' then
      temp_a <= d_in;
      temp_sl1 <= shift_lt_rt;
      temp_sby1 <= shift_by;
    end if;
  end process d_1;

  s_4: process (clk, temp_sby1, temp_sl1, temp_a)
  begin  -- process
    if (temp_sl1 ='1' and (temp_sby1(2) = '1')) then     --shift by 4 bits
      temp_4 <= temp_a ror 4;
      elsif (temp_sl1 ='0' and (temp_sby1(2) = '1')) then
      temp_4 <= temp_a rol 4;
      else temp_4 <= temp_a;
    end if;
  end process s_4;

 d_2: process (clk, rst_a)
  begin  -- process
    if rst_a = '1' then                   -- asynchronous reset (active high)
      temp_b <= "00000000";
    elsif clk'event and clk = '1' then
      temp_b <= temp_4;
      temp_sl2 <= temp_sl1;
      temp_sby2 <= temp_sby1;
    end if;
  end process d_2;

 s_2:  process (clk, temp_sby2, temp_sl2, temp_b)
  begin  -- process
    if (temp_sl2 ='1' and (temp_sby2(1) = '1')) then          --shift by 2 bits
      temp_2 <= temp_b ror 2;
      elsif (temp_sl2 ='0' and (temp_sby2(1) = '1' )) then
      temp_2 <= temp_b rol 2;
      else temp_2 <= temp_b;
    end if;
  end process s_2;

 
  d_3: process (clk, rst_a)
  begin  -- process
    if rst_a = '1' then                   -- asynchronous reset (active high)
      temp_c <= "00000000";
    elsif clk'event and clk = '1' then
      temp_c <= temp_2;
      temp_sl3 <= temp_sl2;
      temp_sby3 <= temp_sby2;
    end if;
  end process d_3;

  s_1:  process (clk, temp_sby3, temp_sl3, temp_c)
  begin  -- process
    if (temp_sl3 ='1' and (temp_sby3(0) = '1')) then        --shift by 1 bit
      temp_1 <= temp_c ror 1;
      elsif (temp_sl3 ='0' and (temp_sby3(0) = '1')) then
      temp_1 <= temp_c rol 1;
      else temp_1 <= temp_c;
    end if;
  end process s_1;
 
  d_4: process (clk, rst_a)
  begin  -- process
    if rst_a = '1' then                   -- asynchronous reset (active high)
      d_out <= "00000000";
    elsif clk'event and clk = '1' then
      d_out <= temp_1;
    end if;
  end process d_4;

end arch;
-----------------------------------------------


Textio code
----------------------------------------------

library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
use ieee.std_logic_textio.all;

library std;
use std.textio.all;

entity barrel_shifter_multi_txtio is
 
end barrel_shifter_multi_txtio;

architecture arch of barrel_shifter_multi_txtio is

  component barrel_shifter_multi
  port (
    d_in        : in  std_logic_vector(7 downto 0);   -- input vector
    d_out       : out std_logic_vector(7 downto 0);   -- shifted output
    shift_lt_rt : in  std_logic;                      -- 0=>left_operation 1=>right_operation
    shift_by    : in  std_logic_vector(2 downto 0);   -- 000=> parallel load other=>shift amount
    clk         : in  std_logic;                      -- clock signal
    rst_a       : in  std_logic);                     -- reset signal

  end component;

signal rst_a : std_logic;
signal shift_lt_rt: std_logic;
signal shift_by : std_logic_vector(2 downto 0);
signal d_out,d_in : std_logic_vector(7 downto 0);
signal clk : std_logic := '1';          -- clk signal

begin  -- arch

u1: barrel_shifter_multi port map (
  rst_a      => rst_a,
  clk        => clk,
  shift_lt_rt   => shift_lt_rt,
  d_in       => d_in,
  shift_by   => shift_by,
  d_out     => d_out);

clk <= not clk after 50 ns;

p1: process
 
  file infile         : text open read_mode is "in_vector.txt";
  file outfile        : text open write_mode is "result.txt";
  variable rline      : line;
  variable wline      : line;
  variable d_in_v     : std_logic_vector(7 downto 0);
  variable rst_a_v    : std_logic;
  variable shift_lt_rt_v : std_logic;
  variable shift_by_v : std_logic_vector(2 downto 0);
 
begin  -- process p1
readline(infile, rline);
write (wline, string'("rst_a"),left,15);
write (wline, string'("shift_lt_rt"),left,15);
write (wline, string'("shift_by"),left,15);
write (wline, string'("d_in"),left,15);
write (wline, string'("d_out"),left,15);

writeline(outfile, wline);

 while not(endfile(infile)) loop
   wait until (clk'event and clk='1');
   readline(infile,rline);
   read(rline, rst_a_v);
   read(rline, shift_lt_rt_v);
   read(rline,shift_by_v);
   read(rline,d_in_v);
 
   rst_a<=rst_a_v ;
   shift_lt_rt<=shift_lt_rt_v;
   shift_by<=shift_by_v ;
   d_in<= d_in_v ;
 
   write(wline,rst_a_v,left,15);
   write(wline,shift_lt_rt_v,left,15);
   write(wline,shift_by_v,left,15);
   write(wline, d_in_v,left ,15);
   write (wline,d_out,left,15);
   writeline(outfile, wline);
 end loop;
 wait;
end process p1;
end arch;

---------------------------------------------------------

in_vector
------------
rst_a shift_lt_rt shift_by d_in
1 0 000 00000000
0 0 001 11110000
0 0 011 11100000
0 0 101 10000111
0 0 110 10000111
0 1 110 10000111
0 1 010 10000111
0 1 101 11100111
0 1 010 10000111
0 1 100 10000111
0 0 100 10010111
0 1 100 10110111
0 0 010 10010111
0 1 100 10011111
0 1 001 10101101
0 0 011 10101101
0 0 110 11100010
0 1 101 11100010
0 0 011 10101101
0 1 010 11100010
0 0 001 11100010
1 0 001 11100010
0 1 001 11110000
0 1 010 11100000
0 1 000 11100000
0 1 000 11110000
0 1 010 11100000
0 1 010 11100000


out_vector
---------------------
rst_a          shift_lt_rt    shift_by       d_in           d_out         
1              0              000            00000000       00000000      
0              0              001            11110000       00000000      
0              0              011            11100000       00000000      
0              0              101            10000111       00000000      
0              0              110            10000111       00000000      
0              1              110            10000111       11100001      
0              1              010            10000111       00000111      
0              1              101            11100111       11110000      
0              1              010            10000111       11100001      
0              1              100            10000111       00011110      
0              0              100            10010111       11100001      
0              1              100            10110111       00111111      
0              0              010            10010111       11100001      
0              1              100            10011111       01111000      
0              1              001            10101101       01111001      
0              0              011            10101101       01111011      
0              0              110            11100010       01011110      
0              1              101            11100010       11111001      
0              0              011            10101101       11010110      
0              1              010            11100010       01101101      
0              0              001            11100010       10111000      
1              0              001            11100010       00010111      
0              1              001            11110000       00000000      
0              1              010            11100000       00000000      
0              1              000            11100000       00000000      
0              1              000            11110000       00000000      
0              1              010            11100000       01111000      
0              1              010            11100000       00111000      

Thursday, April 4, 2013

Vhdl code for barrel shifter with single cycle

library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_arith.all;
use ieee.std_logic_unsigned.all;

entity barrel_shifter is
 
  port (
    d_in        : in  bit_vector(7 downto 0);   -- input vector
    d_out       : out bit_vector(7 downto 0);   -- shifted output
    shift_lt_rt : in  bit;                      -- 0=>left_operation 1=>right_operation
    shift_by    : in  bit_vector(2 downto 0);   -- 000=> parallel load other=>shift amount
    clk         : in  bit;                      -- clock signal
    rst_a       : in  bit);                     -- reset signal

end barrel_shifter;

architecture beh of barrel_shifter is

begin  -- beh
 p1: process (clk,rst_a,shift_by,shift_lt_rt)
variable x,y : bit_vector(7 downto 0);
variable ctrl0,ctrl1,ctrl2 : bit_vector(1 downto 0);
 begin  -- process p1
ctrl0:=shift_by(0) & shift_lt_rt;
ctrl1:=shift_by(1) & shift_lt_rt;
ctrl2:=shift_by(2) & shift_lt_rt;
if(rst_a = '1') then
d_out<="00000000";
elsif(clk'event and clk = '1') then

if (shift_by="000")then
  assert(false) report "Parallel load" severity warning;
elsif(shift_lt_rt='1')then
  assert(false) report "right shift" severity warning;
elsif(shift_lt_rt='0')then
  assert(false) report "left shift" severity warning;
 end if;

case ctrl0 is
  when "00"|"01" =>x:=d_in ;
  when "10" =>x:=d_in(6 downto 0) & d_in(7);
  when "11" =>x:=d_in(0) & d_in(7 downto 1);
  when others => null;
end case;
case ctrl1 is
  when "00"|"01" =>y:=x;
  when "10" =>y:=x(5 downto 0) & x(7 downto 6);
  when "11" =>y:=x(1 downto 0) & x(7 downto 2);
  when others => null;
end case;
case ctrl2 is
  when "00"|"01" =>d_out<=y ;
  when "10"|"11" =>d_out<= y(3 downto 0) & y(7 downto 4);
  when others => null;
end case;
end if;
  end process p1;
end beh;

Barrel shifter with multi cycle vhdl code

library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_arith.all;
use ieee.std_logic_unsigned.all;

entity barrel_shifter_multi is
 
  port (
    d_in        : in  bit_vector(7 downto 0);   -- input vector
    d_out       : out bit_vector(7 downto 0);   -- shifted output
    shift_lt_rt : in  bit;                      -- 0=>left_operation 1=>right_operation
    shift_by    : in  bit_vector(2 downto 0);   -- 000=> parallel load other=>shift amount
    clk         : in  bit;                      -- clock signal
    rst_a       : in  bit);                     -- reset signal

end barrel_shifter_multi;

architecture beh of barrel_shifter_multi is
signal x,y,z : bit_vector(7 downto 0);
signal tmp,tmp2,tmp3 : bit_vector(7 downto 0);
signal ctrl0,ctrl1,ctrl2 : bit_vector(1 downto 0);
begin  -- beh

--ctrl0<=shift_by(0) & shift_lt_rt;
--ctrl1<=shift_by(1) & shift_lt_rt;
--ctrl2<=shift_by(2) & shift_lt_rt;

p1: process (clk, rst_a)
begin  -- process p1
  if rst_a = '1' then                   -- asynchronous reset (active high)
    tmp<="00000000";
  elsif clk'event and clk = '1' then    -- rising clock edge
    tmp<=d_in;
    ctrl0<=shift_by(0) & shift_lt_rt;
  end if;
end process p1;


s1: process (ctrl0,tmp,clk)
begin  -- process p2
case ctrl0 is
  when "00"|"01" =>x<=tmp ;
  when "10" =>x<=tmp(6 downto 0) & tmp(7);
  when "11" =>x<=tmp(0) & tmp(7 downto 1);
  when others => null;
end case;
end process s1;

p2: process (clk, rst_a)
begin  -- process p1
  if rst_a = '1' then                   -- asynchronous reset (active high)
    tmp2<="00000000";
  elsif clk'event and clk = '1' then    -- rising clock edge
    tmp2<=x;
    ctrl1<=shift_by(1) & shift_lt_rt;
  end if;
end process p2;

s2: process (ctrl1,tmp2,clk)
begin  -- process s2
  case ctrl1 is
  when "00"|"01" =>y<=tmp2;
  when "10" =>y<=tmp2(5 downto 0) & tmp2(7 downto 6);
  when "11" =>y<=tmp2(1 downto 0) & tmp2(7 downto 2);
  when others => null;
end case;
end process s2;

p3: process (clk, rst_a)
begin  -- process p1
  if rst_a = '1' then                   -- asynchronous reset (active high)
    tmp3<="00000000";
  elsif clk'event and clk = '1' then    -- rising clock edge
    tmp3<=y;
    ctrl2<=shift_by(2) & shift_lt_rt;
  end if;
end process p3;

s4: process (ctrl2,tmp3,clk)
begin  -- process s4
  case ctrl2 is
  when "00"|"01" =>z<=tmp3 ;
  when "10"|"11" =>z<= tmp3(3 downto 0) & tmp3(7 downto 4);
  when others => null;
end case;

end process s4;

p4: process (clk, rst_a)
begin  -- process p1
  if rst_a = '1' then                   -- asynchronous reset (active high)
    d_out<="00000000";
  elsif clk'event and clk = '1' then    -- rising clock edge
    d_out<=z;
  end if;
end process p4;
end beh;

Tuesday, April 2, 2013

Barrel shifter with rotate left and write vhdl code

library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_arith.all;
use ieee.std_logic_unsigned.all;

entity barrel_shifter5 is
 
  port (
    rst_a       : in  std_logic;                     -- asynchronous reset input
    shift_lt : in  bit ;                                  -- shift by left
    shift_rt     : in  bit ;                                  -- shift by right
    d_in        : in  bit_vector(7 downto 0);        -- parallel data input
    clk         : in  bit;                           -- clock input
    d_out       : out bit_vector(7 downto 0);        -- barrel shifted output
    shift_by    : in  bit_vector(2 downto 0));       -- how much it should be shifted

end barrel_shifter5;

architecture beh of barrel_shifter5 is

--left shifting function
  function shift_lft (constant d :bit_vector(7 downto 0); signal shift1 :bit_vector(2 downto 0))
    return bit_vector is
    begin
       case shift1 is
       when "000" => return d;        --without shifting
       when "001" => return d rol 1;  --shift left by 1
       when "010" => return d rol 2;  --shift left by 2
       when "011" => return d rol 3;  --shift left by 3
       when "100" => return d rol 4;  --shift left by 4
       when "101" => return d rol 5;  --shift left by 5
       when "110" => return d rol 6;  --shift left by 6
       when "111" => return d rol 7;  --shift left by 7
       end case;
    return d;
   end shift_lft;

--right shifting function
   function shift_rgt (constant d :bit_vector(7 downto 0); signal shift1 :bit_vector(2 downto 0))
    return bit_vector is
    begin
       case shift1 is
       when "000" => return d;        --without shifting
       when "001" => return d ror 1;  --shift right by 1
       when "010" => return d ror 2;  --shift right by 2
       when "011" => return d ror 3;  --shift right by 3
       when "100" => return d ror 4;  --shift right by 4
       when "101" => return d ror 5;  --shift right by 5
       when "110" => return d ror 6;  --shift right by 6
       when "111" => return d ror 7;  --shift right by 7
       end case;
    return d;
   end shift_rgt;

                                 
begin  -- beh

shifter: process (clk,rst_a,shift_by,d_in,shift_lt,shift_rt)
variable tmp : bit_vector(7 downto 0);
begin  -- process shifter
 if rst_a = '1' then
    d_out<= "00000000";
    tmp:=d_in;
  elsif clk'event and clk='1' then
  if shift_lt=shift_rt then      -- parallel load
    assert(false) report "parallel load" severity warning;
      tmp:=d_in;
  elsif shift_lt>shift_rt then   -- shift left
    assert(false) report "left operation" severity warning;
      tmp:=shift_lft(tmp,shift_by);
   elsif shift_lt<shift_rt then  -- shift right
    assert(false) report "right operation" severity warning;
      tmp:=shift_rgt(tmp,shift_by);
   end if; 
d_out<=tmp;
end if;
end process shifter;
end beh;

Parity generator with serial input and parallel output vhdl code






library IEEE;
use IEEE.std_logic_1164.all;
use IEEE.std_logic_arith.all;
use IEEE.std_logic_unsigned.all;

entity parity_gen is
 
  port (
    clk       : in  std_logic;
    rst_a     : in  std_logic;
    valid_in  : in  std_logic;
    d_in      : in  std_logic;          -- input serial data stream
    valid_out : out std_logic;
    parity    : out std_logic;
    data_o    : out std_logic_vector (7 downto 0));

end parity_gen;

architecture parity_gen_arch of parity_gen is

  component d_ff is
 
  port (
     rst  : in  std_logic;               -- asynchronous reset
     clk  : in  std_logic;               -- clock
     en   : in  std_logic;               -- control signal 
     d_in : in  std_logic;               -- input data
     q    : out std_logic                -- output data
    );           

  end component;
 
  function parity_gen_func (par : in std_logic_vector (7 downto 0)) return std_logic is
  begin
  return par(0)xor par(1)xor par(2)xor par(3)xor par(4)xor par(5)xor par(6)xor par(7);
  end parity_gen_func;

  signal count : std_logic_vector (2 downto 0) := "000";
  signal temp : std_logic_vector (7 downto 0);

begin  -- parity_gen_arch

   d_ff1: d_ff port map (rst_a, clk, valid_in, d_in, temp(0));
   d_ff2: d_ff port map (rst_a, clk, valid_in, temp(0), temp(1));
   d_ff3: d_ff port map (rst_a, clk, valid_in, temp(1), temp(2));
   d_ff4: d_ff port map (rst_a, clk, valid_in, temp(2), temp(3));
   d_ff5: d_ff port map (rst_a, clk, valid_in, temp(3), temp(4));
   d_ff6: d_ff port map (rst_a, clk, valid_in, temp(4), temp(5));
   d_ff7: d_ff port map (rst_a, clk, valid_in, temp(5), temp(6));
   d_ff8: d_ff port map (rst_a, clk, valid_in, temp(6), temp(7));
  
data_o<= temp;
parity <= parity_gen_func(temp);
  
p1:   process (clk, rst_a)
        begin       
    if rst_a = '1' then                 -- asynchronous reset
      valid_out <= '0';
     
    elsif clk'event and clk ='1' then
    if valid_in = '1' then
        count<= count + '1';   
    end if; 
    if count = "111" then
        valid_out <= '1';
    else
        valid_out <= '0';
    end if;
    end if;
  end process p1;
 
end parity_gen_arch;