-- EE301B Semester Project, Winter 1998
-- 8051 UART (Universal Asynchronous Receiver/Transmitter) model

-- Source : Intel 8051 Family Microprocessors Manual

-- Author : Lingfeng Yuan, Prajakta Kurvey

-- Revision history:

-- 04/05
-- Started writing the code for the UART

-- 04/08
-- implemented the transmission and reception of mode 0 and 1
-- still a lot of errors and assumptions

-- 04/09
-- finished mode 2 and 3
-- looks correct except for the assumptions

-- 19/09
-- changed the divide-by-16 counters

-- 23/09
-- changed the transmitter and receiver processes to be sentitive to a list
-- eliminated all wait statements in them
-- eliminated all bus contention problems

-- package to define some types
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_arith.all;

package mc8051_UART_pkg is
  subtype byte is unsigned (7 downto 0);
  constant sbuf_addr : byte := "10011001";
  constant all_0 : byte := "00000000";
  constant hi_imp : byte := "ZZZZZZZZ";

-- the following type is used to break up the machine cycle
-- into 6 states, with 2 pulses for each state
-- copied from Mayer's program
  type machine_cycle_states is (init, s1p1, s1p2, s2p1, s2p2, s3p1, s3p2,
s4p1, s4p2, s5p1, s5p2, s6p1, s6p2);

end mc8051_UART_pkg;

-- main program for the UART
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_arith.all;
use work.mc8051_UART_pkg.all;

-- these are the interface signals for our stand-alone UART
entity mc8051_UART is
  port (
        cycle_state : in machine_cycle_states;
        p2clk : in std_logic;           -- phase 2 clock
        addr_gb : in byte;              -- global address bus
        data_gb : inout byte := hi_imp; -- global data bus
        rd_gb : in std_logic;           -- global read signal, active high
        wr_gb : in std_logic;           -- global write signal, active high
        indirect_sel : in std_logic;    -- direct or indirect address mode
        tf1 : in std_logic := '0';      -- tf1 is the timer 1 overflow flag
        smod : in std_logic := '0';     -- smod is pcon.7
        scon : in byte;                 -- serial port control SFR
        rxd : inout std_logic := 'H';
        txd : out std_logic := '1';

        tb8_set, tb8_reset : out std_logic := '0';
        rb8_set, rb8_reset : out std_logic := '0';

        ti_set, ri_set : out std_logic := '0';
        acknow : out std_logic := '0');
end entity;

architecture behave of mc8051_UART is

signal to_send, write_to_sbuf : std_logic := '0';

-- some aliases to decompose scon
-- sm_r is reversed serial port mode
alias sm_r : unsigned (2 downto 0) is scon(7 downto 5);
alias ren : std_logic is scon(4);
alias tb8 : std_logic is scon(3);
alias rb8 : std_logic is scon(2);
alias ti : std_logic is scon(1);
alias ri : std_logic is scon(0);

-- serial port buffers
signal sbuf_wr, sbuf_rd : byte := all_0;

-- divide-by-16 counters and their reset signals (rising edge sensitive)
-- tf1_16 is for timer 1 overflow signal
-- p2clk_16 is for phase 2 clock
subtype cnt_type is natural range 0 to 16;
signal tf1_16, p2clk_16 : cnt_type := 0;
signal tf1_16_reset, p2clk_16_reset : std_logic := '0';

signal acknow_wr, acknow_rd : std_logic := '0';
signal txd_wr, txd_rd : std_logic := '1';

begin

-- process to detect write_to_sbuf operation
-- we still need to verify the timing of the execution of the instruction
process begin
wait until wr_gb = '1';
if addr_gb = sbuf_addr and indirect_sel = '0' then      -- CPU writes to serial port
  sbuf_wr <= data_gb;
  to_send <= not to_send;
  wait for 2 ns;
  acknow_wr <= '1';
  wait until wr_gb = '0';
  acknow_wr <= '0';
end if;
end process;

-- we assume that the write_to_sbuf pulse always occurs in s6p2
-- process to align to_send with s6p2 and convert it to a pulse
process begin
  wait on to_send;
  wait until cycle_state = s6p2;
  write_to_sbuf <= '1';
  -- wait for a cycle state
  wait on cycle_state;
  write_to_sbuf <= '0';
end process;

-- process to detect read_from_sbuf operation
-- we still need to verify the timing of the execution of the instruction
process begin
wait until rd_gb = '1';
if addr_gb = sbuf_addr and indirect_sel = '0' then      -- CPU reads from serial port
  data_gb <= sbuf_rd;
  acknow_rd <= '1';
  wait until rd_gb = '0';
  data_gb <= hi_imp;
  acknow_rd <= '0';
end if;
end process;

-- process to resolve acknow_wr and acknow_rd to get acknow
acknow <= acknow_wr or acknow_rd;

-- transmitter process
-- initiated by rising edge of write_to_sbuf generated when CPU writes to sbuf
process (sm_r(2 downto 1), write_to_sbuf, cycle_state, tf1_16, p2clk_16)

variable i : integer := 0;              -- iteration counter
variable sbuf_dup : byte := all_0;      -- internal buffer for sbuf
variable to_send, no_start : bit := '0';

begin

-- if sm_r(2 downto 1) is changed, clear the current process
if sm_r(2 downto 1)'event then to_send := '0'; end if;

if rising_edge(write_to_sbuf) then      -- initiate transmission
  to_send := '1';       -- this signal means transmission in progress
  sbuf_dup := sbuf_wr;  -- fill internal buffer
  i := 0;               -- clear iteration counter
  no_start := '1';      -- still in the write_to_sbuf cycle, don't start
  ti_set <= '0';        -- lower the ti_set signal to create an edge later
end if;

if to_send = '1' then

-- sm_r is reversed sm
-- so mode 1 is "10", mode 2 is "01"
  case sm_r(2 downto 1) is

  when "00" =>

    -- mode 0, 8-bit shift register, Fxtal1/12 (one bit every machine cycle)
    -- shift clock is output through txd
    -- shift clock is low during s3, s4, s5, high during s6, s1, s2
    -- actual data is output through rxd

    if cycle_state'event then
      case cycle_state is
        when s1p1 => if i = 0 then no_start := '0';     -- start iteration
                     elsif i = 9 then                   -- time to stop
                        rxd <= 'H';
                        ti_set <= '1';
                        to_send := '0';
                     end if;
        when s3p1 => if i /= 0 then txd_wr <= '0'; end if;
        when s6p1 => if i /= 0 then txd_wr <= '1'; end if;
        when s6p2 => if no_start = '0' then
                        if i < 8 then rxd <= sbuf_dup(i); end if;
                        i := i + 1;
                     end if;
        when others => null;
      end case;
    end if;

  when "10" =>

    -- mode 1, 8-bit UART, baud rate set by timer 1

    -- assumes that shift happens at the rollovers
    if tf1_16'event and tf1_16 = 0 then
      case i is
        when 0 => txd_wr <= '0';        -- start bit
        when 9 => txd_wr <= '1';        -- 9th bit ('1')
                  -- not sure when ti goes high, 9 or 10
                  ti_set <= '1';
        when 10 => null;                -- stop bit, keep high
        when 11 => to_send := '0';      -- time to stop
        when others => txd_wr <= sbuf_dup(i-1);         -- shift the byte out
      end case;
      i := i + 1;
    end if;

  when "01" =>

    -- mode 2, 9-bit UART, Fxtal1/64 or Fxtal1/32

    -- assumes that shift happens at the rollovers
    if p2clk_16'event and p2clk_16 = 0 then
      case i is
        when 0 => txd_wr <= '0';        -- start bit
        when 9 => txd_wr <= tb8;        -- 9th bit
        when 10 => txd_wr <= '1';       -- stop bit
                   ti_set <= '1';
        when 11 => to_send := '0';      -- time to stop
        when others => txd_wr <= sbuf_dup(i-1);         -- shift the byte out
      end case;
      i := i+1;
    end if;

  when "11" =>

    -- mode 3, 9-bit UART, baud rate set by timer 1

    -- assumes that shift happens at the rollovers
    if tf1_16'event and tf1_16 = 0 then
      case i is
        when 0 => txd_wr <= '0';        -- start bit
        when 9 => txd_wr <= tb8;        -- 9th bit
        when 10 => txd_wr <= '1';       -- stop bit
                   ti_set <= '1';
        when 11 => to_send := '0';      -- time to stop
        when others => txd_wr <= sbuf_dup(i-1);         -- shift the byte out
      end case;
      i := i+1;
    end if;

  when others => null;

  end case;

end if;

end process;

-- process to receive data from outside
-- reception start conditions:
-- for mode 0 the condition is ri = '0' and ren = '1'
-- for other modes the condition is ren = '1' and falling edge of rxd
process (sm_r(2 downto 1), cycle_state, tf1_16, p2clk_16, rxd)

variable i : integer := 0;              -- iteration counter
variable samp1, samp2, samp3, rcvd_bit : std_logic;
variable sbuf_dup : byte;               -- internal buffer for sbuf
-- indicate whether reception is in session
variable rcv_in_session : std_logic := '0';

begin

-- if sm_r(2 downto 1) is changed, clear the current process
if sm_r(2 downto 1)'event then rcv_in_session := '0'; end if;

case sm_r(2 downto 1) is

  when "00" =>

    -- mode 0, 8-bit shift register, Fxtal1/12
    -- shift clock is output through txd
    -- shift clock is low during s3, s4, s5, high during s6, s1, s2
    -- actual data is sampled in through rxd during s5p2

  if cycle_state'event and ri = '0' and ren = '1' then
    if rcv_in_session = '0' then        -- initiate reception
      rcv_in_session := '1';
      i := 0;
      ri_set <= '0';    -- lower ri_set signal to create an edge later
    else                                -- already in reception
      case cycle_state is
        when s1p1 => if i = 9 then      -- time to stop
                        sbuf_rd <= sbuf_dup;
                        ri_set <= '1';  -- set ri
                        rcv_in_session := '0';
                     end if;
        when s3p1 => if i /= 0 then txd_rd <= '0'; end if;
        -- assume that ri is cleared after s5p2 in the cycle
        when s5p2 => if i /= 0 then sbuf_dup(i-1) := rxd; end if;
                     i := i + 1;
        when s6p1 => if i /= 0 then txd_rd <= '1'; end if;
        when others => null;
      end case;
    end if;
  end if;

  when "10" =>

    -- mode 1, 8-bit UART, baud rate set by timer 1

    -- we can change this falling edge detection into sampling
    if falling_edge(rxd) and (ren = '1') and (rcv_in_session = '0') then
      rcv_in_session := '1';
      tf1_16_reset <= '1';      -- reset the counter immediately
      i := 0;
      rb8_set <= '0';
      rb8_reset <= '0';
      ri_set <= '0';
    end if;

    if tf1_16'event and (rcv_in_session = '1') then
      case tf1_16 is
      when 7 => samp1 := rxd;           -- first sample
      when 8 => samp2 := rxd;           -- second sample
      when 9 =>
        samp3 := rxd;           -- third sample

        -- take the value which appears at least twice, for noise rejection
        if samp1 = samp2 or samp2 = samp3 then rcvd_bit := samp2;
        else rcvd_bit := samp1;
        end if;

        if i = 0 then                   -- start bit
          if rcvd_bit /= '0' then       -- false start bit, start over
            rcv_in_session := '0';
            tf1_16_reset <= '0';
          end if;
        elsif i = 9 then                -- stop bit
          -- two conditions to meet for successful reception completion
          if ri = '0' and (sm_r(0) = '0' or rcvd_bit = '1') then
            sbuf_rd <= sbuf_dup;
            -- save rcvd_bit in rb8
            if rcvd_bit = '1' then rb8_set <= '1';
            else rb8_reset <= '1';
            end if;
            ri_set <= '1';
          end if;
          rcv_in_session := '0';
          tf1_16_reset <= '0';
        else sbuf_dup(i-1) := rcvd_bit; -- data bits
        end if;

        i := i + 1;
      when others => null;
      end case;
    end if;

  when "01" =>

    -- mode 2, 9-bit UART, Fxtal1/64 or Fxtal1/32

    -- we can change this falling edge detection into sampling
    if falling_edge(rxd) and (ren = '1') and (rcv_in_session = '0') then
      rcv_in_session := '1';
      p2clk_16_reset <= '1';    -- reset the counter
      i := 0;
      rb8_set <= '0';
      rb8_reset <= '0';
      ri_set <= '0';
    end if;

    if p2clk_16'event and (rcv_in_session = '1') then
      case p2clk_16 is
      when 7 => samp1 := rxd;           -- first sample
      when 8 => samp2 := rxd;           -- second sample
      when 9 =>
        samp3 := rxd;           -- third sample

        -- take the value which appears at least twice, for noise rejection
        if samp1 = samp2 or samp2 = samp3 then rcvd_bit := samp2;
        else rcvd_bit := samp1;
        end if;

        if i = 0 then                   -- start bit
          if rcvd_bit /= '0' then       -- false start bit, start over
            rcv_in_session := '0';
            p2clk_16_reset <= '0';
          end if;
        elsif i = 9 then                -- stop bit
          -- two conditions to meet for successful reception completion
          if ri = '0' and (sm_r(0) = '0' or rcvd_bit = '1') then
            sbuf_rd <= sbuf_dup;
            -- save rcvd_bit in rb8
            if rcvd_bit = '1' then rb8_set <= '1';
            else rb8_reset <= '1';
            end if;
            ri_set <= '1';
          end if;
          rcv_in_session := '0';
          p2clk_16_reset <= '0';
        else sbuf_dup(i-1) := rcvd_bit; -- data bits
        end if;

        i := i + 1;
      when others => null;
      end case;
    end if;

  when "11" =>

    -- mode 3, 9-bit UART, baud rate set by timer 1

    -- we can change this falling edge detection into sampling
    if falling_edge(rxd) and (ren = '1') and (rcv_in_session = '0') then
      rcv_in_session := '1';
      tf1_16_reset <= '1';      -- reset the counter
      i := 0;
      rb8_set <= '0';
      rb8_reset <= '0';
      ri_set <= '0';
    end if;

    if tf1_16'event and (rcv_in_session = '1') then
      case tf1_16 is
      when 7 => samp1 := rxd;           -- first sample
      when 8 => samp2 := rxd;           -- second sample
      when 9 =>
        samp3 := rxd;           -- third sample

        -- take the value which appears at least twice, for noise rejection
        if samp1 = samp2 or samp2 = samp3 then rcvd_bit := samp2;
        else rcvd_bit := samp1;
        end if;

        if i = 0 then                   -- start bit
          if rcvd_bit /= '0' then       -- false start bit, start over
            rcv_in_session := '0';
            tf1_16_reset <= '0';
          end if;
        elsif i = 9 then                -- stop bit
          -- two conditions to meet for successful reception completion
          if ri = '0' and (sm_r(0) = '0' or rcvd_bit = '1') then
            sbuf_rd <= sbuf_dup;
            -- save rcvd_bit in rb8
            if rcvd_bit = '1' then rb8_set <= '1';
            else rb8_reset <= '1';
            end if;
            ri_set <= '1';
          end if;
          rcv_in_session := '0';
          tf1_16_reset <= '0';
        else sbuf_dup(i-1) := rcvd_bit; -- data bits
        end if;

        i := i + 1;
      when others => null;
      end case;
    end if;

  when others => null;

end case;

end process;

-- the rxd signal has got two drivers: outside and transmitter
-- in mode 0 both can drive rxd
-- in other modes only outside drives rxd
-- when transmitter is not driving it outputs 'H'

-- process to resolve the txd signal
-- it's got two drivers: transmitter and receiver
-- in mode 0 both transmitter and receiver can drive txd
-- in other modes only transmitter drives txd
-- when one is not driving txd, it outputs '1'
txd <= txd_wr and txd_rd;

-- process to generate the divide-by-16 counter of timer 1 overflow signal
-- the clock of this counter is 16 times slower than the timer 1 overflow signal
-- we don't know in which cycle_state tf1 will be set
-- so have to synchronize it with s1p1
process (tf1, cycle_state, tf1_16_reset)
variable tf1_flag : bit := '0';
variable tf1_half : bit := '0';
begin

-- rising edge of tf1_16_reset clears the counter
-- could be level-triggered
if rising_edge(tf1_16_reset) then tf1_16 <= 0; end if;

if rising_edge(tf1) then tf1_flag := '1'; end if;

if cycle_state'event and cycle_state = s1p1 and tf1_flag = '1' then
  if smod = '0' then                    -- cut the frequency in half
    tf1_half := not tf1_half;
  end if;

  if not (smod = '0' and tf1_half = '1') then   -- increment the counter
    tf1_16 <= (tf1_16 + 1) mod 16;
    tf1_flag := '0';
  end if;
end if;

end process;

-- process to generate the divide-by-16 counter of the phase 2 clock
-- phase 2 clock is twice as slow as the xtal1 clock
process (p2clk, p2clk_16_reset)
variable p2clk_half : bit := '0';
begin

-- rising edge of p2clk_16_reset clears the counter
-- could be level-triggered
if rising_edge(p2clk_16_reset) then p2clk_16 <= 0; end if;

-- it could be rising edge depending on how it aligns with cycle_state
if falling_edge(p2clk) then
  if smod = '0' then            -- cut the frequency in half
    p2clk_half := not p2clk_half;
  end if;

  if not (smod = '0' and p2clk_half = '1') then -- increment the counter
    p2clk_16 <= (p2clk_16 + 1) mod 16;
  end if;
end if;

end process;

end behave;

-- EE301B Semester Project, Winter 1998
-- 8051 UART (Universal Asynchronous Receiver/Transmitter) model test bench

-- Source : Intel 8051 Family Microprocessors Manual

-- Author : Lingfeng Yuan, Prajakta Kurvey

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

entity uarttb is
end entity;

architecture test of uarttb is

-- this is the period of the xtal1 input
-- usually it is 11.059MHz or 6MHz
-- for debugging purpose, we set the period to 10 ns
constant T : time := 10 ns;
signal xtal1, p2clk : std_logic := '0';
signal cycle_state : machine_cycle_states := init;

signal wr_gb, rd_gb : std_logic := '0';
signal addr_gb : byte := all_0;
signal data_gb : byte := hi_imp;
-- indirect_sel signal remains at '0' all the time
signal indirect_sel : std_logic := '0';
signal acknow : std_logic := '0';

signal tf1, smod : std_logic := '0';
signal rxd : std_logic := 'Z';
signal txd : std_logic := 'Z';

signal scon : byte := all_0;
signal sm_r : unsigned (2 downto 0) := "000";
signal ren : std_logic := '1';
signal tb8 : std_logic := '0';
signal rb8 : std_logic := '0';
signal ti : std_logic := '0';
signal ri : std_logic := '1';

signal tb8_set, tb8_reset : std_logic := '0';
signal rb8_set, rb8_reset : std_logic := '0';
signal ti_set, ri_set : std_logic := '0';

signal cpu_tb8_set, cpu_tb8_reset : std_logic := '0';
signal cpu_rb8_set, cpu_rb8_reset : std_logic := '0';
signal cpu_ti_set, cpu_ri_set : std_logic := '0';
signal cpu_ti_reset, cpu_ri_reset : std_logic := '0';

signal reception_stage : std_logic := '0';

begin

-- process to generate the xtal1 signal
xtal1 <= not xtal1 after T/2;

-- process to advance machine state at every falling edge of xtal1
process begin
wait until falling_edge(xtal1);
case cycle_state is
  when init => cycle_state <= s1p1;
  when s1p1 => cycle_state <= s1p2;
  when s1p2 => cycle_state <= s2p1;
  when s2p1 => cycle_state <= s2p2;
  when s2p2 => cycle_state <= s3p1;
  when s3p1 => cycle_state <= s3p2;
  when s3p2 => cycle_state <= s4p1;
  when s4p1 => cycle_state <= s4p2;
  when s4p2 => cycle_state <= s5p1;
  when s5p1 => cycle_state <= s5p2;
  when s5p2 => cycle_state <= s6p1;
  when s6p1 => cycle_state <= s6p2;
  when s6p2 => cycle_state <= s1p1;
end case;
end process;

-- process to generate the phase 2 clock
process begin
  wait until falling_edge(xtal1);
  p2clk <= not p2clk;
end process;

-- process to generate the timer 1 overflow signal
-- in the manual it doesn't say in which machine state tf1 is set
-- we assume that tf1 is set in s6p1
-- it is aligned with s1p1 inside UART so doesn't matter
-- we assume that timer 1 is set in auto-reload mode
-- it overflows every 4 machines cycles
process (cycle_state)
variable i : integer := 0;
begin
  if cycle_state = s6p1 then
    if i = 1 then
      tf1 <= '1';
      i := 0;
    else
      tf1 <= '0';
      i := i + 1;
    end if;
  end if;
end process;

smod <= '1';

-- process to do the set/reset of tb8
process (tb8_set, tb8_reset, cpu_tb8_set, cpu_tb8_reset) begin
  if rising_edge(tb8_set) or rising_edge(cpu_tb8_set) then tb8 <= '1';
  elsif rising_edge(tb8_reset) or rising_edge(cpu_tb8_reset) then tb8 <=
'0';
  end if;
end process;

-- process to do the set/reset of rb8
process (rb8_set, rb8_reset, cpu_rb8_set, cpu_rb8_reset) begin
  if rising_edge(rb8_set) or rising_edge(cpu_rb8_set) then rb8 <= '1';
  elsif rising_edge(rb8_reset) or rising_edge(cpu_rb8_reset) then rb8 <=
'0';
  end if;
end process;

-- process to do the set/reset of ti
process (ti_set, cpu_ti_set, cpu_ti_reset) begin
  if rising_edge(ti_set) or rising_edge(cpu_ti_set) then ti <= '1';
  elsif rising_edge(cpu_ti_reset) then ti <= '0';
  end if;
end process;

-- process to do the set/reset of ri
process (ri_set, cpu_ri_set, cpu_ri_reset) begin
  if rising_edge(ri_set) or rising_edge(cpu_ri_set) then ri <= '1';
  elsif rising_edge(cpu_ri_reset) then ri <= '0';
  end if;
end process;

dut: entity work.mc8051_UART(behave)
  port map (
        cycle_state => cycle_state,
        p2clk => p2clk,
        addr_gb => addr_gb,
        data_gb => data_gb,
        rd_gb => rd_gb,
        wr_gb => wr_gb,
        indirect_sel => indirect_sel,
        tf1 => tf1,
        smod => smod,
        acknow => acknow,
        scon => scon,
        rxd => rxd,
        txd => txd,
        tb8_set => tb8_set,
        tb8_reset => tb8_reset,
        rb8_set => rb8_set,
        rb8_reset => rb8_reset,
        ti_set => ti_set,
        ri_set => ri_set);

scon <= sm_r & ren & tb8 & rb8 & ti & ri;

process begin
  reception_stage <= '0';
  wait for 100000 ns;
  reception_stage <= '1';
  wait for 100000 ns;
  reception_stage <= '0';
  wait;
end process;

-- process to generate the outside rxd signal
process begin
  rxd <= 'H';
  wait until rising_edge(reception_stage);

  -- generate rxd for mode 0
  for i in 0 to 4 loop
    rxd <= '0';
    wait for 12 * T;
    rxd <= '1';
    wait for 12 * T;
  end loop;

  -- generate rxd for mode 1
  for i in 0 to 5 loop
    rxd <= '0';
    wait for 32 * T;
    rxd <= '1';
    wait for 32 * T;
  end loop;

  -- generate rxd for mode 2
  for i in 0 to 10 loop
    rxd <= '0';
    wait for 384 * T;
    rxd <= '1';
    wait for 384 * T;
  end loop;

  wait;
end process;


-- in the manual the time to access the buses seem to take place in s2p1 and 
-- s5p1 assume that the rd and wr signals appears during s5p1 
process
variable data : byte := all_0;
begin

  -- set the serial port in mode 0 first
  sm_r <= "000";
  -- clear ti bit for subsequent transmission
  cpu_ti_reset <= '1';
  wait until cycle_state = s5p1;
  cpu_ti_reset <= '0';

  -- write a byte to sbuf
  addr_gb <= sbuf_addr;
  data_gb <= "01010101";
  wait for 2 ns;
  wr_gb <= '1';
  wait until acknow = '1';
  wr_gb <= '0';
  addr_gb <= all_0;
  data_gb <= hi_imp;

  -- wait until transmission is finished
  wait until ti = '1';

  wait until cycle_state = s3p2;
  -- set the serial port in mode 2
  sm_r <= "010";
  -- clear ti bit for subsequent transmission
  cpu_ti_reset <= '1';
  wait until cycle_state = s5p1;
  cpu_ti_reset <= '0';

  -- write a byte to sbuf
  addr_gb <= sbuf_addr;
  data_gb <= "01010101";
  wait for 2 ns;
  wr_gb <= '1';
  wait until acknow = '1';
  wr_gb <= '0';
  addr_gb <= hi_imp;
  data_gb <= hi_imp;

  -- wait until transmission is finished
  wait until ti = '1';

  wait until cycle_state = s3p2;
  -- set the serial port in mode 1
  sm_r <= "100";
  -- clear ti bit for subsequent transmission
  cpu_ti_reset <= '1';
  wait until cycle_state = s5p1;
  cpu_ti_reset <= '0';

  -- write a byte to sbuf
  addr_gb <= sbuf_addr;
  data_gb <= "01010101";
  wait for 2 ns;
  wr_gb <= '1';
  wait until acknow = '1';
  wr_gb <= '0';
  addr_gb <= hi_imp;
  data_gb <= hi_imp;

  -- wait until transmission is finished
  wait until ti = '1';

  wait until cycle_state = s3p2;
  -- set the serial port in mode 3
  sm_r <= "110";
  -- clear ti bit for subsequent transmission
  cpu_ti_reset <= '1';
  wait until cycle_state = s5p1;
  cpu_ti_reset <= '0';

  -- write a byte to sbuf
  addr_gb <= sbuf_addr;
  data_gb <= "01010101";
  wait for 2 ns;
  wr_gb <= '1';
  wait until acknow = '1';
  wr_gb <= '0';
  addr_gb <= hi_imp;
  data_gb <= hi_imp;

  -- wait until transmission is finished
  wait until ti = '1';
  sm_r <= "000";

  -- align with the rxd input process
  wait until rising_edge(reception_stage);

  wait until cycle_state = s6p2;
  -- clear ri bit for reception
  cpu_ri_reset <= '1';

  wait until ri = '1';
  cpu_ri_reset <= '0';
  -- read a byte from sbuf
  wait until cycle_state = s5p1;
  addr_gb <= sbuf_addr;
  rd_gb <= '1';
  wait until acknow = '1';
  data := data_gb;
--  assert data = "01010101" report "data incorrect";
  data := all_0;
  rd_gb <= '0';
  addr_gb <= all_0;

  wait until cycle_state = s3p2;
  sm_r <= "010";
  wait until cycle_state = s6p2;
  -- clear ri bit for reception
  cpu_ri_reset <= '1';

  wait until ri = '1';
  cpu_ri_reset <= '0';
  -- read a byte from sbuf
  wait until cycle_state = s5p1;
  addr_gb <= sbuf_addr;
  rd_gb <= '1';
  wait until acknow = '1';
  data := data_gb;
--  assert data = "01010101" report "data incorrect";
  data := all_0;
  rd_gb <= '0';
  addr_gb <= all_0;

  wait until cycle_state = s3p2;
  sm_r <= "100";
  wait until cycle_state = s6p2;
  -- clear ri bit for reception
  cpu_ri_reset <= '1';

  wait until ri = '1';
  cpu_ri_reset <= '0';
  -- read a byte from sbuf
  wait until cycle_state = s5p1;
  addr_gb <= sbuf_addr;
  rd_gb <= '1';
  wait until acknow = '1';
  data := data_gb;
--  assert data = "01010101" report "data incorrect";
  data := all_0;
  rd_gb <= '0';
  addr_gb <= all_0;

  wait until cycle_state = s3p2;
  sm_r <= "110";
  wait until cycle_state = s6p2;
  -- clear ri bit for reception
  cpu_ri_reset <= '1';

  wait until ri = '1';
  cpu_ri_reset <= '0';
  -- read a byte from sbuf
  wait until cycle_state = s5p1;
  addr_gb <= sbuf_addr;
  rd_gb <= '1';
  wait until acknow = '1';
  data := data_gb;
--  assert data = "01010101" report "data incorrect";
  data := all_0;
  rd_gb <= '0';
  addr_gb <= all_0;

  wait;

end process;

end test;

<div align="center"><br /><script type="text/javascript"><!--
google_ad_client = "pub-7293844627074885";
//468x60, Created at 07. 11. 25
google_ad_slot = "8619794253";
google_ad_width = 468;
google_ad_height = 60;
//--></script>
<script type="text/javascript" src="http://pagead2.googlesyndication.com/pagead/show_ads.js">
</script><br />&nbsp;</div>