]> git.the-white-hart.net Git - vhdl/commitdiff
Update with lots of work, need to organize
authorRyan <>
Wed, 17 Sep 2025 19:32:23 +0000 (14:32 -0500)
committerRyan <>
Wed, 17 Sep 2025 19:32:23 +0000 (14:32 -0500)
24 files changed:
libraries/nexys2/mem_wb8_0_opt.vhd [new file with mode: 0644]
libraries/nexys2/tests/test_sim_mem_wb8_0.vhd
libraries/rs232/rs232_rx_opt.vhd [new file with mode: 0644]
libraries/rs232/rs232_tx_opt.vhd [new file with mode: 0644]
libraries/rs232/rs232_uart.vhd
libraries/rs232/rs232_uart_opt.vhd [new file with mode: 0644]
libraries/rs232/tests/test_rx_opt.vhd [new file with mode: 0644]
libraries/rs232/tests/test_tx_opt.vhd [new file with mode: 0644]
libraries/rs232/tests/test_uart.vhd
libraries/simulated/delay_edges.vhd
libraries/simulated/sim_js28f128j3d75.vhd
libraries/simulated/sim_memory.vhd [new file with mode: 0644]
libraries/simulated/tests/test_attrs.vhd [new file with mode: 0644]
libraries/simulated/tests/test_sim_memory.vhd [new file with mode: 0644]
libraries/simulated/tests/test_simflash.vhd
libraries/utility/fifo.vhd
libraries/utility/multiclk_ram.vhd [new file with mode: 0644]
libraries/utility/reg_file.vhd [new file with mode: 0644]
libraries/utility/reg_file_1w2r.vhd [new file with mode: 0644]
libraries/vga/vga_tiler.vhd
libraries/vga/vga_tiler_opt.vhd [new file with mode: 0644]
projects/cpu_0/asm/int_test2.asm
projects/cpu_0/nexys2.vhd
projects/cpu_0/nexys2_opt.vhd [new file with mode: 0644]

diff --git a/libraries/nexys2/mem_wb8_0_opt.vhd b/libraries/nexys2/mem_wb8_0_opt.vhd
new file mode 100644 (file)
index 0000000..b11818d
--- /dev/null
@@ -0,0 +1,184 @@
+--------------------------------------------------------------------------------
+-- mem_wb8_0 - Simple, non-caching 8-bit interface to Nexys2 onboard memory
+--
+-- Endianness of the interface is undefined, but for storage within the 16-bit
+-- memory, little-endian ordering is used (even bytes are stored in the least-
+-- significant byte, odd bytes are stored in the most-significant byte).
+--------------------------------------------------------------------------------
+-- WISHBONE DATASHEET
+--
+-- Wishbone specification used: Rev B.3
+-- Interface type: device
+-- Port size: 8-bit
+-- Operand sizes: 8-bit
+-- Endianness: undefined (port size same as granularity)
+-- Data transfer sequence: undefined
+-- Clock constraints: max 50 MHz
+-- Signals:
+-- * rst_i
+-- * clk_i
+-- * fls_cyc_i (CYC_I for flash)
+-- * ram_cyc_i (CYC_I for RAM)
+-- * stb_i
+-- * we_i
+-- * ack_o
+-- * adr_i (24-bit)
+-- * dat_i (8-bit)
+-- * dat_o (8-bit)
+--------------------------------------------------------------------------------
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.std_logic_misc.all;
+use ieee.numeric_std.all;
+
+library unisim;
+use unisim.vcomponents.all;
+
+
+entity mem_wb8_0_opt is
+       generic (
+               CYCLES_ACTIVE: std_logic_vector(3 downto 0) := "0110";
+               CYCLES_TOTAL:  std_logic_vector(3 downto 0) := "1000"
+       );
+       port (
+               -- Wishbone SYSCON
+               rst_i:       in  std_logic;
+               clk_i:       in  std_logic;
+
+               -- Wishbone system interface
+               fls_cyc_i:   in  std_logic;
+               ram_cyc_i:   in  std_logic;
+               stb_i:       in  std_logic;
+               we_i:        in  std_logic;
+               ack_o:       out std_logic;
+               adr_i:       in  std_logic_vector(23 downto 0);
+               dat_i:       in  std_logic_vector(7 downto 0);
+               dat_o:       out std_logic_vector(7 downto 0);
+
+               -- Memory interface
+               MemOE:       out std_logic;
+               MemWR:       out std_logic;
+               RamAdv:      out std_logic;
+               RamCS:       out std_logic;
+               RamClk:      out std_logic;
+               RamCRE:      out std_logic;
+               RamUB:       out std_logic;
+               RamLB:       out std_logic;
+               RamWait:     in  std_logic;
+               FlashRp:     out std_logic;
+               FlashCS:     out std_logic;
+               FlashStSts:  in  std_logic;
+               MemAdr:      out std_logic_vector(23 downto 1);
+               MemDB_i:     in  std_logic_vector(15 downto 0);  -- Inbound: from memory to device
+               MemDB_o:     out std_logic_vector(15 downto 0)   -- Outbound: from device to memory
+       );
+end mem_wb8_0_opt;
+
+
+architecture behavioral of mem_wb8_0_opt is
+
+       signal state_idle:       std_logic;
+       signal state_total:      std_logic;
+
+       signal state_idle_next:  std_logic;
+       signal state_total_next: std_logic;
+
+       signal count_cycles:     std_logic_vector(3 downto 0);
+       signal count_start:      std_logic;
+       signal count_done:       std_logic;
+
+       signal mem_enable:     std_logic;
+
+       -- Replacement for original cyc_i when separating cyc for ram and flash
+       signal cyc_i:          std_logic;
+
+begin
+
+       cyc_i <= fls_cyc_i or ram_cyc_i;
+
+       process (rst_i, clk_i, state_idle_next, state_total_next)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               state_idle  <= '1';
+                               state_total <= '0';
+                       else
+                               state_idle  <= state_idle_next;
+                               state_total <= state_total_next;
+                       end if;
+               end if;
+       end process;
+
+       process (state_idle, state_total, cyc_i, stb_i, we_i, count_done)
+       begin
+               state_idle_next  <= state_idle;
+               state_total_next <= state_total;
+               count_start <= '0';
+
+               ack_o       <= '0';
+
+               mem_enable  <= '0';
+               MemOE       <= '1';
+               MemWR       <= '1';
+
+               if state_idle = '1' then
+                       -- Idle, waiting for transaction request
+                       if cyc_i = '1' and stb_i = '1' then
+                               state_idle_next <= '0';
+                               count_start     <= '1';
+                       end if;
+               elsif state_total = '0' then
+                       -- Memory active
+                       mem_enable <= '1';
+                       MemOE      <= we_i;
+                       MemWR      <= not we_i;
+
+                       if count_done = '1' then
+                               ack_o <= '1';
+                               state_total_next <= '1';
+                       end if;
+               else
+                       -- Memory inactive
+                       if count_done = '1' then
+                               state_idle_next  <= '1';
+                               state_total_next <= '0';
+                       end if;
+               end if;
+       end process;
+
+       -- Little-endian memory interface
+       RamCS                <= not (mem_enable and ram_cyc_i);
+       RamAdv               <= '0';
+       RamClk               <= '0';
+       RamCRE               <= '0';
+       RamUB                <= not adr_i(0);
+       RamLB                <=     adr_i(0);
+       FlashCS              <= not (mem_enable and fls_cyc_i);
+       FlashRp              <= '1';
+       MemAdr               <= adr_i(23 downto 1);
+       MemDB_o(15 downto 8) <= dat_i when adr_i(0) = '1' else (others => '0');
+       MemDB_o( 7 downto 0) <= dat_i;
+       dat_o                <= MemDB_i(15 downto 8) when adr_i(0) = '1' else MemDB_i(7 downto 0);
+       --dat_o                <= mdr_reg(15 downto 8) when adr_i(0) = '1' else mdr_reg(7 downto 0);
+
+
+       -- Cycle counter
+       count_cycles <= CYCLES_TOTAL when state_total = '1' else CYCLES_ACTIVE;
+
+       e_count: srl16
+               generic map (INIT => x"0000")
+               port map (
+                       clk => clk_i,
+
+                       a0  => count_cycles(0),
+                       a1  => count_cycles(1),
+                       a2  => count_cycles(2),
+                       a3  => count_cycles(3),
+
+                       d   => count_start,
+
+                       q   => count_done
+               );
+
+end behavioral;
index 60c142ea234b99ee03096b38ea9de96abbe60203..0b91c175eeed2f24427444f749a0ca82edaef914 100644 (file)
@@ -82,6 +82,7 @@ begin
                wait until ack_o = '1';
                fls_cyc_i <= '0';
                stb_i     <= '0';
+               wait for clk_i_period * 2;
 
                -- Read from RAM
                test      <= RD_RAM;
@@ -96,7 +97,7 @@ begin
                wait;
        end process;
 
-       uut: entity work.mem_wb8_0
+       uut: entity work.mem_wb8_0_opt
                port map (
                        rst_i       => rst_i,
                        clk_i       => clk_i,
@@ -110,7 +111,7 @@ begin
                        dat_i       => dat_i,
                        dat_o       => dat_o,
 
-                       wait_cycles => wait_cycles,
+                       --wait_cycles => wait_cycles,
 
                        MemOE       => MemOE,
                        MemWR       => MemWR,
diff --git a/libraries/rs232/rs232_rx_opt.vhd b/libraries/rs232/rs232_rx_opt.vhd
new file mode 100644 (file)
index 0000000..1873f1e
--- /dev/null
@@ -0,0 +1,240 @@
+--------------------------------------------------------------------------------
+-- rs232_rx - receiver for RS232 serial interface
+--
+-- rst_i must be held active for at least 16 clk_i cycles before deasserting
+-- clk_i must be greater than 16x clk_baud_in
+-- clk_baud_in must be 16x the bit rate
+-- clk_baud_in must be active for only one clk_i cycle at a time
+-- parity_out includes stop bits
+-- num_bits_in includes start and stop bits
+--------------------------------------------------------------------------------
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+use ieee.std_logic_misc.all;
+
+library unisim;
+use unisim.vcomponents.all;
+
+
+entity rs232_rx_opt is
+       port (
+               rst_i:       in  std_logic;
+               clk_i:       in  std_logic;
+
+               stb_o:       out std_logic;
+               ack_i:       in  std_logic;
+               dat_o:       out std_logic_vector(11 downto 0);
+
+               clk_baud_in: in  std_logic;  -- 16x bit rate
+               num_bits_in: in  std_logic_vector(3 downto 0);  -- Number of bits in a frame
+               missed_out:  out std_logic;
+               parity_out:  out std_logic;  -- parity of all bits (including start and stop)
+
+               rx_in:       in  std_logic
+       );
+end rs232_rx_opt;
+
+
+architecture behavioral of rs232_rx_opt is
+
+       type state_t is (S_READY, S_SHIFT, S_FLUSH_1, S_FLUSH_0);
+       signal state_reg:   state_t;
+       signal next_state:  state_t;
+
+       signal ready:       std_logic;
+       signal flush:       std_logic;
+       signal shift:       std_logic;
+
+       -- Bit timing signals
+       signal baud_tick:   std_logic;
+       signal baud_start:  std_logic;
+       signal baud_sample: std_logic;
+       signal baud_done:   std_logic;
+
+       -- Bit counting signals
+       signal count_tick:  std_logic;
+       signal count_in:    std_logic;
+       signal count_done:  std_logic;
+       signal count_flush: std_logic;
+
+       -- Input conditioning
+       signal rx_reg:      std_logic;
+
+       -- Output registers
+       signal shift_reg:   std_logic_vector(15 downto 0);  -- max 1 start, 8 data, 1 parity, 2 stop
+       signal ready_reg:   std_logic;
+       signal parity_reg:  std_logic;
+       signal missed_reg:  std_logic;
+
+begin
+
+       ----------------------------------------------------------------------------
+       -- State machine
+
+       process (rst_i, clk_i, next_state)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               state_reg <= S_READY;
+                       else
+                               state_reg <= next_state;
+                       end if;
+               end if;
+       end process;
+
+       process (state_reg, rx_reg, clk_baud_in, baud_done, count_flush)
+       begin
+               next_state <= state_reg;
+               baud_start <= '0';
+               count_in   <= '0';
+               flush      <= '0';
+               shift      <= '0';
+               ready      <= '0';
+
+               case state_reg is
+                       when S_READY =>
+                               if rx_reg = '0' and clk_baud_in = '1' then
+                                       baud_start  <= '1';
+                                       next_state  <= S_SHIFT;
+                               end if;
+
+                       when S_SHIFT =>
+                               baud_start <= baud_done;
+                               count_in   <= '1';
+                               if count_done = '1' then
+                                       next_state <= S_FLUSH_1;
+                               end if;
+
+                       when S_FLUSH_1 =>
+                               flush <= '1';
+                               -- Continue shifting until the start bit is in position zero
+                               shift <= not count_flush;
+                               if count_flush = '1' then
+                                       ready      <= '1';
+                                       next_state <= S_FLUSH_0;
+                               end if;
+
+                       when S_FLUSH_0 =>
+                               flush <= '1';
+                               if count_flush = '0' then
+                                       next_state <= S_READY;
+                               end if;
+
+                       when others =>
+                               next_state <= S_READY;
+               end case;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Control interface
+
+       process (rst_i, clk_i, ack_i, ready, ready_reg)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               ready_reg  <= '0';
+                               missed_reg <= '0';
+                       else
+                               if ack_i = '1' then
+                                       ready_reg  <= '0';
+                                       missed_reg <= '0';
+                               end if;
+
+                               if ready = '1' then
+                                       missed_reg <= ready_reg and (not ack_i);
+                                       ready_reg  <= '1';
+                               end if;
+                       end if;
+               end if;
+       end process;
+
+       stb_o      <= ready_reg;
+       missed_out <= missed_reg;
+       parity_out <= parity_reg;
+       dat_o      <= shift_reg(11 downto 0);
+
+
+       ----------------------------------------------------------------------------
+       -- Bit timer, bit counter, data shifter, and parity checker
+
+       -- Count 16ths of a bit clock to decide when to sample and when to shift
+       baud_tick <= rst_i or flush or clk_baud_in;
+       e_baud: srlc16e
+               generic map (INIT => x"0000")
+               port map (
+                       clk => clk_i,
+                       ce  => baud_tick,
+
+                       a0  => '1',
+                       a1  => '1',
+                       a2  => '1',
+                       a3  => '0',
+
+                       d   => baud_start,
+
+                       q   => baud_sample,
+                       q15 => baud_done
+               );
+
+       -- Count bits as we receive them to decide when done
+       count_tick <= rst_i or flush or (clk_baud_in and baud_done);
+       e_count: srlc16e
+               generic map (INIT => x"0000")
+               port map (
+                       clk => clk_i,
+                       ce  => count_tick,
+
+                       a0  => num_bits_in(0),
+                       a1  => num_bits_in(1),
+                       a2  => num_bits_in(2),
+                       a3  => num_bits_in(3),
+
+                       d   => count_in,
+
+                       q   => count_done,
+                       q15 => count_flush
+               );
+
+       -- Sample and shift data bits
+       process (rst_i, clk_i, clk_baud_in, baud_sample, rx_reg, shift_reg)
+       begin
+               if rising_edge(clk_i) then
+                       if (baud_sample = '1' and clk_baud_in = '1') or shift = '1' then
+                               shift_reg <= rx_reg & shift_reg(shift_reg'high downto 1);
+                       end if;
+               end if;
+       end process;
+
+       -- Sample bits and compute parity
+       process (rst_i, clk_i, clk_baud_in, baud_sample, parity_reg)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               parity_reg <= '0';
+                       elsif baud_sample = '1' and clk_baud_in = '1' then
+                               parity_reg <= parity_reg xor rx_reg;
+                       end if;
+               end if;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Input conditioning
+
+       -- Synchronize the incoming external signal to the internal clock
+       process (clk_i, rx_in)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               rx_reg <= '1';  -- Prevent false start bis after reset
+                       else
+                               rx_reg <= rx_in;
+                       end if;
+               end if;
+       end process;
+
+
+end behavioral;
diff --git a/libraries/rs232/rs232_tx_opt.vhd b/libraries/rs232/rs232_tx_opt.vhd
new file mode 100644 (file)
index 0000000..ac8d035
--- /dev/null
@@ -0,0 +1,175 @@
+--------------------------------------------------------------------------------
+-- rs232_tx - transmitter for RS232 serial interface
+--
+-- rst_i must be held active for at least 16 clk_i cycles before deasserting
+-- clk_i must be greater than 16x clk_baud_in
+-- clk_baud_in must be 16x the bit rate
+-- clk_baud_in must be active for only one clk_i cycle at a time
+-- parity_out includes stop bits
+-- num_bits_in includes start and stop bits
+--------------------------------------------------------------------------------
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+use ieee.std_logic_misc.all;
+
+library unisim;
+use unisim.vcomponents.all;
+
+
+entity rs232_tx_opt is
+       port (
+               rst_i:         in  std_logic;
+               clk_i:         in  std_logic;
+
+               stb_i:         in  std_logic;
+               ack_o:         out std_logic;
+               dat_i:         in  std_logic_vector(11 downto 0);
+
+               clk_baud_in:   in  std_logic;
+               num_bits_in:   in  std_logic_vector(3 downto 0);
+
+               tx_out:        out std_logic
+       );
+end rs232_tx_opt;
+
+
+architecture behavioral of rs232_tx_opt is
+
+       type state_t is (S_READY, S_SHIFT, S_FLUSH_0, S_FLUSH_1);
+       signal state_reg:   state_t;
+       signal next_state:  state_t;
+
+       -- Bit timing signals
+       signal baud_tick:   std_logic;
+       signal baud_start:  std_logic;
+       signal baud_done:   std_logic;
+
+       -- Bit counting signals
+       signal count_tick:  std_logic;
+       signal count_in:    std_logic;
+       signal count_done:  std_logic;
+       signal count_flush: std_logic;
+
+       -- Other signals
+       signal flush:       std_logic;
+       signal shift_latch: std_logic;
+       signal shift_reg:   std_logic_vector(11 downto 0);
+
+begin
+
+       ----------------------------------------------------------------------------
+       -- State machine
+
+       process (rst_i, clk_i, next_state)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               state_reg <= S_READY;
+                       else
+                               state_reg <= next_state;
+                       end if;
+               end if;
+       end process;
+
+       process (state_reg, stb_i, shift_reg, clk_baud_in, baud_done, count_done, count_flush)
+       begin
+               next_state  <= state_reg;
+
+               tx_out      <= '1';
+               ack_o       <= '0';
+
+               shift_latch <= '0';
+               flush       <= '0';
+
+               baud_start  <= '0';
+               count_in    <= '0';
+
+               case state_reg is
+                       when S_READY =>
+                               if stb_i = '1' and clk_baud_in = '1' then
+                                       ack_o <= '1';
+                                       next_state  <= S_SHIFT;
+                                       shift_latch <= '1';
+                                       baud_start  <= '1';
+                               end if;
+
+                       when S_SHIFT =>
+                               tx_out     <= shift_reg(0);
+                               baud_start <= baud_done;
+                               count_in   <= '1';
+                               if count_done = '1' then
+                                       next_state <= S_FLUSH_1;
+                               end if;
+
+                       when S_FLUSH_1 =>
+                               flush <= '1';
+                               if count_flush = '1' then
+                                       next_state <= S_FLUSH_0;
+                               end if;
+
+                       when S_FLUSH_0 =>
+                               flush <= '1';
+                               if count_flush = '0' then
+                                       next_state <= S_READY;
+                               end if;
+
+                       when others =>
+                               next_state <= S_READY;
+               end case;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Shift register, bit counter, and parity generator
+
+       -- Count 16ths of a bit clock to decide when to sample and when to shift
+       baud_tick <= rst_i or flush or clk_baud_in;
+       e_baud: srl16e
+               generic map (INIT => x"0000")
+               port map (
+                       clk => clk_i,
+                       ce  => baud_tick,
+
+                       a0  => '1',
+                       a1  => '1',
+                       a2  => '1',
+                       a3  => '1',
+
+                       d   => baud_start,
+
+                       q   => baud_done
+               );
+
+       -- Count bits as we receive them to decide when done
+       count_tick <= rst_i or flush or (clk_baud_in and baud_done);
+       e_count: srlc16e
+               generic map (INIT => x"0000")
+               port map (
+                       clk => clk_i,
+                       ce  => count_tick,
+
+                       a0  => num_bits_in(0),
+                       a1  => num_bits_in(1),
+                       a2  => num_bits_in(2),
+                       a3  => num_bits_in(3),
+
+                       d   => count_in,
+
+                       q   => count_done,
+                       q15 => count_flush
+               );
+
+       process (clk_i, shift_latch, clk_baud_in, baud_done, dat_i, shift_reg)
+       begin
+               if rising_edge(clk_i) then
+                       if shift_latch = '1' then
+                               shift_reg <= dat_i;
+                       elsif clk_baud_in = '1' and baud_done = '1' then
+                               shift_reg <= '0' & shift_reg(shift_reg'high downto 1);
+                       end if;
+               end if;
+       end process;
+
+end behavioral;
index 04c6c75a32a230d8dc535396a39560c9d7e94c80..bf7dfa7f6dd933e54f9f1f24d3a6dc0dabe8d5e9 100644 (file)
@@ -233,7 +233,7 @@ begin
        -- Separate strobe signal for data register access
        data_stb <= (cyc_i and stb_i) when adr_i = ADDR_DATA else '0';
 
-       -- Deliver data stroe to TX or RX based on transaction direction
+       -- Deliver data strobe to TX or RX based on transaction direction
        txqh_stb <= data_stb when we_i = '1' else '0';
        rxqt_ack <= data_stb when we_i = '0' else '0';
 
diff --git a/libraries/rs232/rs232_uart_opt.vhd b/libraries/rs232/rs232_uart_opt.vhd
new file mode 100644 (file)
index 0000000..27ee32a
--- /dev/null
@@ -0,0 +1,438 @@
+--------------------------------------------------------------------------------
+-- rs232_uart - Wishbone UART for RS232 serial interface
+--------------------------------------------------------------------------------
+-- TODO: https://eecs.umich.edu/courses/doing_dsp/handout/SRL16E.pdf
+--       Play with using shift-registers to make this more dense
+--
+--    +---+---+---+---+---+---+---+---+
+--    | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
+--    +---+---+---+---+---+---+---+---+
+-- 0  |LB |BRK|   |STP|POD|PE |TXE|RXE| CTRL
+--    +---+-------+---+---+---+---+---+
+-- 1  |       DIVISOR LOW BYTE        | BAUDL
+--    +-------------------------------+
+-- 2  |       DIVISOR HIGH BYTE       | BAUDH
+--    +---+---+---+---+---+---+---+---+
+-- 3  |BER|FER|PER|OER|TXE|TXR|RXF|RXR| IMASK
+--    +---+---+---+---+---+---+---+---+
+-- 4  |BER|FER|PER|OER|TXE|TXR|RXF|RXR| IFLAG
+--    +---+---+---+---+---+---+---+---+
+-- 5  |             DATA              | DATA
+--    +-------------------------------+
+-- 6  |          (RESERVED)           |
+--    +-------------------------------+
+-- 7  |          (RESERVED)           |
+--    +-------------------------------+
+--
+-- CTRL register bits:
+-- RXE - Enable receive logic
+-- TXE - Enable transmit logic
+-- PE  - Enable parity generation and checking
+-- POD - Generate and check for odd parity (else even)
+-- STP - Number of stop bits: clear -> 1, set -> 2
+-- BRK - Create break condition by holding TX line low (not yet implemented)
+-- LB  - Loopback enable
+--
+-- IMASK/IFLAG register bits:
+-- RXR - Receiver has at least one byte ready
+--       Deasserts when all DATA read
+-- RXF - Receiver FIFO is full
+--       Deasserts on read from DATA
+-- TXR - Transmitter ready to accept at least one byte
+--       Deasserts when TX FIFO is full
+-- TXE - Transmitter FIFO is empty
+--       Deasserts on write to DATA
+-- OER - Receiver FIFO overrun, at least one byte was lost due to lack of space
+--       Write one to clear
+-- PER - Receiver parity error
+--       Write one to clear
+-- FER - Receiver framing error, either start or stop bit was incorrect
+--       Write one to clear
+--       (not yet implemented)
+-- BER - Break condition detected (RX line was held low for a full byte)
+--       Write one to clear
+--       (not yet implemented)
+--
+-- BAUDL/BAUDH:
+-- 16-bit clock divisor representing the number of system clock cycles per bit
+--
+-- For 50MHz clock:
+-- +------+---------+
+-- | Baud | Divisor |
+-- +------+---------+
+-- | 9600 | 0x1458  |
+-- +------+---------+
+--
+-- Notes:
+--
+-- User must check flags before reading/writing DATA register to ensure data is
+-- available in RX or space is available in TX, otherwise undefined data will be
+-- returned or written data will be lost.
+--
+-- TODO: Use generics for FIFO capacities
+-- TODO: Fill in baud divisor table for more rates
+-- TODO: Detect and generate break conditions
+-- TODO: Add framing checks
+--------------------------------------------------------------------------------
+-- WISHBONE DATASHEET
+--
+-- Wishbone specification used: Rev B.3
+-- Interface type: device
+-- Port size: 8-bit
+-- Operand sizes: 8-bit
+-- Endianness: undefined (port size same as granularity)
+-- Data transfer sequence: undefined
+-- Clock constraints: none
+-- Signals:
+-- * rst_i
+-- * clk_i
+-- * cyc_i
+-- * stb_i
+-- * we_i
+-- * ack_o
+-- * adr_i (3-bit)
+-- * dat_i (8-bit)
+-- * dat_o (8-bit)
+--------------------------------------------------------------------------------
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.std_logic_misc.all;
+use ieee.numeric_std.all;
+
+library utility;
+library work;
+
+
+entity rs232_uart_opt is
+       port (
+               -- Wishbone SYSCON
+               rst_i:        in  std_logic;
+               clk_i:        in  std_logic;
+
+               -- Wishbone bus slave interface
+               cyc_i:        in  std_logic;
+               stb_i:        in  std_logic;
+               we_i:         in  std_logic;
+               ack_o:        out std_logic;
+               adr_i:        in  std_logic_vector(2 downto 0);
+               dat_i:        in  std_logic_vector(7 downto 0);
+               dat_o:        out std_logic_vector(7 downto 0);
+
+               -- Queueing signals
+               rx_ready:     out std_logic;  -- At least one byte ready in the RX FIFO
+               rx_full:      out std_logic;  -- The RX FIFO is full
+               tx_ready:     out std_logic;  -- At least one byte free in the TX FIFO
+               tx_empty:     out std_logic;  -- The TX FIFO is empty
+
+               -- Error signals
+               err_break:    out std_logic;  -- Break condition detected
+               err_framing:  out std_logic;  -- RX stop bit incorrect
+               err_parity:   out std_logic;  -- RX parity incorrect
+               err_overflow: out std_logic;  -- Byte received with no space in queue
+
+               -- RS232 interface
+               tx:           out std_logic;
+               rx:           in  std_logic
+       );
+end rs232_uart_opt;
+
+
+architecture behavioral of rs232_uart_opt is
+
+       -- Register addresses
+       constant ADDR_CTRL:    std_logic_vector(2 downto 0) := "000";
+       constant ADDR_BAUDL:   std_logic_vector(2 downto 0) := "001";
+       constant ADDR_BAUDH:   std_logic_vector(2 downto 0) := "010";
+       constant ADDR_IMASK:   std_logic_vector(2 downto 0) := "011";
+       constant ADDR_IFLAG:   std_logic_vector(2 downto 0) := "100";
+       constant ADDR_DATA:    std_logic_vector(2 downto 0) := "101";
+
+       -- Control register
+       signal ctrl_reg:       std_logic_vector(7 downto 0);
+       signal rx_en:          std_logic;
+       signal tx_en:          std_logic;
+       signal parity_en:      std_logic;
+       signal parity_odd:     std_logic;
+       signal stop_bits:      std_logic;
+       signal do_break:       std_logic;
+       signal loopback:       std_logic;
+       signal num_bits:       std_logic_vector(3 downto 0);
+
+       -- Baud rate generation
+       signal divisor_reg:    std_logic_vector(15 downto 0) := (others => '0');
+       signal baud_reg:       std_logic_vector(15 downto 0) := (others => '0');
+       signal clk_baud:       std_logic;
+
+       -- Interrupts and mask register
+       signal iflags:         std_logic_vector(7 downto 0);
+       signal imask_reg:      std_logic_vector(7 downto 0);
+
+       -- Tx signals
+       signal txqh_stb:       std_logic;
+       signal txqh_ack:       std_logic;
+       --signal txqh_dat:     std_logic;  -- Comes from dat_i
+       signal txqt_stb:       std_logic;
+       signal txqt_ack:       std_logic;
+       signal txqt_dat:       std_logic_vector(7 downto 0);
+       signal txq_empty:      std_logic;
+       signal txq_full:       std_logic;
+
+       signal tx_rst:         std_logic;
+       signal tx_dat:         std_logic_vector(11 downto 0);
+       signal tx_internal:    std_logic;
+
+       -- Rx signals
+       signal rxqh_stb:       std_logic;
+       signal rxqh_ack:       std_logic;
+       signal rxqh_dat:       std_logic_vector(7 downto 0);
+       signal rxqt_stb:       std_logic;
+       signal rxqt_ack:       std_logic;
+       signal rxqt_dat:       std_logic_vector(7 downto 0);
+       signal rxq_empty:      std_logic;
+       signal rxq_full:       std_logic;
+
+       signal rx_rst:         std_logic;
+       signal rx_stb:         std_logic;
+       signal rx_ack:         std_logic;
+       signal rx_dat:         std_logic_vector(11 downto 0);
+       signal rx_stop_bit:    std_logic;
+       signal rx_parity_bit:  std_logic;  -- Received parity bit
+       signal rx_data_bits:   std_logic_vector(7 downto 0);
+       signal rx_start_bit:   std_logic;
+       signal rx_parity_comp: std_logic;  -- Computed parity
+       signal rx_missed:      std_logic;
+       signal rx_missed_reg:  std_logic;  -- Latched overflow error
+       signal rx_parity_reg:  std_logic;  -- Latched parity error
+       signal rx_framing_reg: std_logic;  -- Latched framing error
+       signal rx_internal:    std_logic;
+
+       signal data_stb:       std_logic;
+
+begin
+
+       -- Wishbone bus
+       process (rst_i, clk_i, cyc_i, stb_i, we_i, adr_i, dat_i, rx_ack)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               ctrl_reg    <= (others => '0');
+                               divisor_reg <= (others => '0');
+                               imask_reg   <= (others => '0');
+
+                               -- IFLAGS
+                               rx_missed_reg  <= '0';
+                               rx_parity_reg  <= '0';
+                               rx_framing_reg <= '0';
+                       else
+                               if cyc_i = '1' and stb_i = '1' and we_i = '1' then
+                                       case adr_i is
+                                               when ADDR_CTRL  => ctrl_reg <= dat_i;
+                                               when ADDR_BAUDL => divisor_reg( 7 downto 0) <= dat_i;
+                                               when ADDR_BAUDH => divisor_reg(15 downto 8) <= dat_i;
+                                               when ADDR_IMASK => imask_reg <= dat_i;
+                                               when ADDR_IFLAG =>
+                                                       rx_missed_reg  <= rx_missed_reg  and (not dat_i(4));
+                                                       rx_parity_reg  <= rx_parity_reg  and (not dat_i(5));
+                                                       rx_framing_reg <= rx_framing_reg and (not dat_i(6));
+                                               when ADDR_DATA  => null;
+                                               when others     => null;
+                                       end case;
+                               end if;
+
+                               -- Latch interrupt flags when a value is accepted into the queue
+                               -- This prevents us from relatching the flag if the queue is full
+                               if rx_ack = '1' and rx_missed = '1' then
+                                       rx_missed_reg <= '1';
+                               end if;
+                               if rx_ack = '1' and parity_en = '1' and (parity_odd xor rx_parity_comp) = '1' then
+                                       rx_parity_reg <= '1';
+                               end if;
+
+                       end if;
+               end if;
+       end process;
+
+       -- Separate strobe signal for data register access
+       data_stb <= (cyc_i and stb_i) when adr_i = ADDR_DATA else '0';
+
+       -- Deliver data strobe to TX or RX based on transaction direction
+       txqh_stb <= data_stb when we_i = '1' else '0';
+       rxqt_ack <= data_stb when we_i = '0' else '0';
+
+       -- All registers respond to the host immediately
+       -- If no data is available for data reads or no space is available for data
+       -- writes then the transaction gets eaten.  It's up to the user to check the
+       -- flags before attempting data access.
+       ack_o <= '1';
+
+       -- Output multiplexer
+       with adr_i select dat_o <=
+               ctrl_reg                 when ADDR_CTRL,
+               divisor_reg( 7 downto 0) when ADDR_BAUDL,
+               divisor_reg(15 downto 8) when ADDR_BAUDH,
+               imask_reg                when ADDR_IMASK,
+               iflags                   when ADDR_IFLAG,
+               rxqt_dat                 when ADDR_DATA,
+               (others => '1')          when others;
+
+       -- Internal control signals
+       rx_en        <= ctrl_reg(0);
+       tx_en        <= ctrl_reg(1);
+       parity_en    <= ctrl_reg(2);
+       parity_odd   <= ctrl_reg(3);
+       stop_bits    <= ctrl_reg(4);
+       do_break     <= ctrl_reg(6);
+       loopback     <= ctrl_reg(7);
+
+       -- Interrupt flags and signals
+       iflags <= '0'            &
+                 rx_framing_reg &
+                 rx_parity_reg  &
+                 rx_missed_reg  &
+                 txq_empty      &
+                 (not txq_full) &
+                 rxq_full       &
+                 (not rxq_empty);
+
+       err_break    <= iflags(7) and imask_reg(7);
+       err_framing  <= iflags(6) and imask_reg(6);
+       err_parity   <= iflags(5) and imask_reg(5);
+       err_overflow <= iflags(4) and imask_reg(4);
+       tx_empty     <= iflags(3) and imask_reg(3);
+       tx_ready     <= iflags(2) and imask_reg(2);
+       rx_full      <= iflags(1) and imask_reg(1);
+       rx_ready     <= iflags(0) and imask_reg(0);
+
+       -- Input-output logic
+       tx <= '1' when tx_en = '0'
+                 else '0' when do_break = '1'
+                          else tx_internal;
+
+       rx_internal <= '1' when rx_en = '0'
+                          else tx_internal when loopback = '1'
+                                           else rx;
+
+       -- Number of bits based on parity and stop bit settings
+       process (parity_en, stop_bits)
+               variable temp: std_logic_vector(1 downto 0);
+       begin
+               temp := parity_en & stop_bits;
+               case temp is
+                       when "00"   => num_bits <= "1001";
+                       when "01"   => num_bits <= "1010";
+                       when "10"   => num_bits <= "1010";
+                       when "11"   => num_bits <= "1011";
+                       when others => num_bits <= (others => 'X');
+               end case;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Transmitter and FIFO
+
+       tx_rst <= rst_i or (not tx_en);
+
+       tx_dat(11)         <= '1';
+       tx_dat(10)         <= '1';
+       tx_dat(9)          <= (xor_reduce(txqt_dat) xor parity_odd) when parity_en = '1' else '1';
+       tx_dat(8 downto 1) <= txqt_dat;
+       tx_dat(0)          <= '0';
+
+       e_tx: entity work.rs232_tx_opt
+               port map (
+                       rst_i       => tx_rst,
+                       clk_i       => clk_i,
+
+                       stb_i       => txqt_stb,
+                       ack_o       => txqt_ack,
+                       dat_i       => tx_dat,
+
+                       clk_baud_in => clk_baud,
+                       num_bits_in => num_bits,
+
+                       tx_out      => tx_internal
+               );
+
+
+       e_tx_fifo: entity utility.fifo_16
+               generic map (WIDTH => 8)
+               port map (
+                       rst_i    => tx_rst,
+                       clk_i    => clk_i,
+
+                       h_stb_i  => txqh_stb,
+                       h_ack_o  => txqh_ack,
+                       h_dat_i  => dat_i,
+
+                       t_stb_o  => txqt_stb,
+                       t_ack_i  => txqt_ack,
+                       t_dat_o  => txqt_dat,
+
+                       is_empty => txq_empty,
+                       is_full  => txq_full
+               );
+
+
+       ----------------------------------------------------------------------------
+       -- Receiver and FIFO
+
+       rx_rst <= rst_i or (not tx_en);
+
+       e_rx: entity work.rs232_rx_opt
+               port map (
+                       rst_i       => rx_rst,
+                       clk_i       => clk_i,
+
+                       stb_o       => rx_stb,
+                       ack_i       => rx_ack,
+                       dat_o       => rx_dat,
+
+                       clk_baud_in => clk_baud,
+                       num_bits_in => num_bits,
+                       missed_out  => rx_missed,
+                       parity_out  => rx_parity_comp,
+
+                       rx_in       => rx_internal
+               );
+
+       rx_stop_bit   <= rx_dat(9) when parity_en = '0' else rx_dat(10);
+       rx_parity_bit <= rx_dat(9);
+       rx_data_bits  <= rx_dat(8 downto 1);
+       rx_start_bit  <= rx_dat(0);
+
+
+       e_rx_fifo: entity utility.fifo_16
+               generic map (WIDTH => 8)
+               port map (
+                       rst_i    => rx_rst,
+                       clk_i    => clk_i,
+
+                       h_stb_i  => rx_stb,
+                       h_ack_o  => rx_ack,
+                       h_dat_i  => rx_data_bits,
+
+                       t_stb_o  => rxqt_stb,
+                       t_ack_i  => rxqt_ack,
+                       t_dat_o  => rxqt_dat,
+
+                       is_empty => rxq_empty,
+                       is_full  => rxq_full
+               );
+
+
+       ----------------------------------------------------------------------------
+       -- Baud rate generator
+       process (clk_i, baud_reg, divisor_reg)
+       begin
+               if rising_edge(clk_i) then
+                       if clk_baud = '1' then
+                               baud_reg <= divisor_reg;
+                       else
+                               baud_reg <= std_logic_vector(unsigned(baud_reg) - 1);
+                       end if;
+               end if;
+       end process;
+       clk_baud <= '1' when baud_reg = x"0000" else '0';
+
+end behavioral;
diff --git a/libraries/rs232/tests/test_rx_opt.vhd b/libraries/rs232/tests/test_rx_opt.vhd
new file mode 100644 (file)
index 0000000..d992e72
--- /dev/null
@@ -0,0 +1,121 @@
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+
+library work;
+
+
+entity test_rx_opt is
+end test_rx_opt;
+
+
+architecture behavioral of test_rx_opt is
+
+       signal rst:      std_logic;
+       signal clk:      std_logic;
+
+       signal stb:      std_logic;
+       signal ack:      std_logic;
+       signal dat:      std_logic_vector(11 downto 0);
+
+       signal clk_baud: std_logic;
+       signal missed:   std_logic;
+       signal parity:   std_logic;
+
+       signal rx:       std_logic;
+
+begin
+
+       p_test: process
+       begin
+               -- Initial values
+               ack <= '0';
+
+               -- Reset
+               rst <= '1';
+               wait for 100 ns;
+               rst <= '0';
+
+               -- Wait for received data
+               wait until stb = '1';
+               ack <= '1';
+               wait for 20 ns;
+               ack <= '0';
+
+               wait;
+       end process;
+
+
+       p_rs232: process
+       begin
+               rx <= '1';
+               wait for 500 us;
+
+               -- 1 start bit
+               rx <= '0';
+               wait for 104 us;
+
+               -- 8 data bits
+               rx <= '1';
+               wait for 104 us;
+               rx <= '1';
+               wait for 104 us;
+               rx <= '0';
+               wait for 104 us;
+               rx <= '0';
+               wait for 104 us;
+               rx <= '0';
+               wait for 104 us;
+               rx <= '1';
+               wait for 104 us;
+               rx <= '0';
+               wait for 104 us;
+               rx <= '1';
+               wait for 104 us;
+
+               -- 0 parity bits
+
+               -- 2 stop bits
+               rx <= '1';
+               wait for 208 us;
+
+               wait;
+       end process;
+
+
+       e_dut: entity work.rs232_rx_opt
+               port map (
+                       rst_i       => rst,
+                       clk_i       => clk,
+
+                       stb_o       => stb,
+                       ack_i       => ack,
+                       dat_o       => dat,
+
+                       clk_baud_in => clk_baud,
+                       num_bits_in => "1001",
+                       missed_out  => missed,
+                       parity_out  => parity,
+
+                       rx_in       => rx
+               );
+
+
+       p_baud: process
+       begin
+               clk_baud <= '0';
+               wait for 6.5 us;
+               clk_baud <= '1';
+               wait for 20 ns;
+       end process;
+
+
+       p_clk: process
+       begin
+               clk <= '0';
+               wait for 10 ns;
+               clk <= '1';
+               wait for 10 ns;
+       end process;
+
+end;
diff --git a/libraries/rs232/tests/test_tx_opt.vhd b/libraries/rs232/tests/test_tx_opt.vhd
new file mode 100644 (file)
index 0000000..1851951
--- /dev/null
@@ -0,0 +1,81 @@
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+
+library work;
+
+
+entity test_tx_opt is
+end test_tx_opt;
+
+
+architecture behavioral of test_tx_opt is
+
+       signal rst:      std_logic;
+       signal clk:      std_logic;
+       signal stb:      std_logic;
+       signal ack:      std_logic;
+       signal dat:      std_logic_vector(11 downto 0);
+       signal clk_baud: std_logic;
+       signal tx:       std_logic;
+
+begin
+
+       p_test: process
+       begin
+               -- Initial values
+               stb <= '0';
+
+               -- Reset
+               rst <= '1';
+               wait for 100 ns;
+               rst <= '0';
+               wait for 100 ns;
+               
+               -- Transmit value
+               dat <= "111010001010";
+               stb <= '1';
+               if ack = '0' then
+                       wait until ack = '1';
+               end if;
+               wait for 20 ns;
+               stb <= '0';
+
+               wait;
+       end process;
+
+
+       e_dut: entity work.rs232_tx_opt
+               port map (
+                       rst_i       => rst,
+                       clk_i       => clk,
+
+                       stb_i       => stb,
+                       ack_o       => ack,
+                       dat_i       => dat,
+
+                       clk_baud_in => clk_baud,
+                       num_bits_in => "1001",
+
+                       tx_out      => tx
+               );
+
+
+       p_baud: process
+       begin
+               clk_baud <= '0';
+               wait for 6.5 us;
+               clk_baud <= '1';
+               wait for 20 ns;
+       end process;
+
+
+       p_clk: process
+       begin
+               clk <= '0';
+               wait for 10 ns;
+               clk <= '1';
+               wait for 10 ns;
+       end process;
+
+end;
index 27f1145093b0a122e22058381d91e4cb45a03c68..b7229b5bd8c67505c5350629b90b80a047e72620 100644 (file)
@@ -1,6 +1,8 @@
 library ieee;
 use ieee.std_logic_1164.all;
 
+library work;
+
  
 entity test_uart is
 end test_uart;
@@ -47,7 +49,7 @@ begin
 
                -- Reset
                rst_i <= '1';
-               wait for clk_i_period*2;
+               wait for clk_i_period*16;
                rst_i <= '0';
 
                -- Configure
@@ -55,7 +57,7 @@ begin
                stb_i <= '1';
                we_i  <= '1';
                adr_i <= "001";
-               dat_i <= x"58";
+               dat_i <= x"46";--x"58";
                if ack_o = '0' then wait until ack_o = '1'; end if;
                wait until rising_edge(clk_i);
                cyc_i <= '0';
@@ -68,7 +70,7 @@ begin
                stb_i <= '1';
                we_i  <= '1';
                adr_i <= "010";
-               dat_i <= x"14";
+               dat_i <= x"01";--x"14";
                if ack_o = '0' then wait until ack_o = '1'; end if;
                wait until rising_edge(clk_i);
                cyc_i <= '0';
@@ -114,36 +116,36 @@ begin
 
                -- 1 start bit
                rx <= '0';
-               wait for 100 us;
+               wait for 104 us;
 
                -- 8 data bits
                rx <= '1';
-               wait for 100 us;
+               wait for 104 us;
                rx <= '1';
-               wait for 100 us;
+               wait for 104 us;
                rx <= '0';
-               wait for 100 us;
+               wait for 104 us;
                rx <= '0';
-               wait for 100 us;
+               wait for 104 us;
                rx <= '0';
-               wait for 100 us;
+               wait for 104 us;
                rx <= '1';
-               wait for 100 us;
+               wait for 104 us;
                rx <= '0';
-               wait for 100 us;
+               wait for 104 us;
                rx <= '1';
-               wait for 100 us;
+               wait for 104 us;
 
                -- 0 parity bits
 
                -- 2 stop bits
                rx <= '1';
-               wait for 200 us;
+               wait for 208 us;
 
                wait;
        end process;
 
-       uut: entity work.rs232_uart
+       uut: entity work.rs232_uart_opt
                port map (
                        rst_i        => rst_i,
                        clk_i        => clk_i,
@@ -160,10 +162,10 @@ begin
                        rx_full      => rx_full,
                        tx_ready     => tx_ready,
                        tx_empty     => tx_empty,
-                       break_err    => break_err,
-                       framing_err  => framing_err,
-                       parity_err   => parity_err,
-                       overflow_err => overflow_err,
+                       err_break    => break_err,
+                       err_framing  => framing_err,
+                       err_parity   => parity_err,
+                       err_overflow => overflow_err,
 
                        tx           => tx,
                        rx           => rx
index 8cb08564389b022689aaa8f45f88b2b3f0a618e5..5bf472e3c074d6d78d938b7e72b3c42bdda299d8 100644 (file)
@@ -17,15 +17,19 @@ architecture behavioral of delay_edges is
        signal mask: std_logic;
 begin
 
-       delayed_a: if D_RISE > D_FALL generate
-               mask <= sig_in'delayed(D_RISE) and sig_in'delayed(D_FALL);
-       end generate;
-
-       delayed_b: if D_RISE <= D_FALL generate
-               mask <= sig_in'delayed(D_RISE) or sig_in'delayed(D_FALL);
-       end generate;
-
-       sig_out <= sig_in when mask = 'U' else mask;
+       process (sig_in)
+       begin
+               if mask = 'U' then
+                       mask <= sig_in;
+               end if;
+               if sig_in'event and sig_in = '1' then
+                       mask <= '1' after D_RISE;
+               end if;
+               if sig_in'event and sig_in = '0' then
+                       mask <= '0' after D_FALL;
+               end if;
+       end process;
+       sig_out <= mask;
 
 end behavioral;
 
index 03d042cdad4c7ccc22fc3a4b2fa4b6ec8bcf4e76..a024d7eda7980d7953fd4e63afc5245146aa3717 100644 (file)
@@ -97,37 +97,114 @@ architecture behavioral of sim_js28f128j3d75 is
        ----------------------------------------------------------------------------
        -- Useful internal signals
 
-       signal internal_ce_n: std_logic;
-       signal internal_we_n: std_logic;
+       signal internal_ce_n:   std_logic;
+       signal internal_we_n:   std_logic;
 
        ----------------------------------------------------------------------------
-       -- Status signals
+       -- Array value
 
-       signal sts_ready:     std_logic;
+       shared variable flash_array: sparse_t;
+       signal array_word:      std_logic_vector(15 downto 0);
 
        ----------------------------------------------------------------------------
-       -- Array value
+       -- Device Information
 
-       shared variable flash_array: sparse_t;
-       signal array_word:    std_logic_vector(15 downto 0);
+       signal id_word:         std_logic_vector(15 downto 0);
+
+       ----------------------------------------------------------------------------
+       -- Status Register
+
+       signal sts_word:        std_logic_vector(15 downto 0);
+
+       signal sts_ready:       std_logic;
+       signal sts_susp_erase:  std_logic;
+       signal sts_error_erase: std_logic;
+       signal sts_error_prog:  std_logic;
+       signal sts_error_vpen:  std_logic;
+       signal sts_susp_prog:   std_logic;
+       signal sts_error_lock:  std_logic;
+
+       ----------------------------------------------------------------------------
+       -- CFI Query
+
+       signal cfi_word:        std_logic_vector(15 downto 0);
 
        ----------------------------------------------------------------------------
        -- Output value
 
-       signal word:          std_logic_vector(15 downto 0);
-       signal word_x:        std_logic_vector(15 downto 0);
-       signal word_xz:       std_logic_vector(15 downto 0);
+       type read_state_t is (R_ARRAY, R_ID, R_STATUS, R_CFI);
+       signal read_state_cur:  read_state_t;
+
+       signal word:            std_logic_vector(15 downto 0);
+       signal word_x:          std_logic_vector(15 downto 0);
+       signal word_xz:         std_logic_vector(15 downto 0);
+
+       signal xmask_rp:        std_logic;
+       signal xmask_byte:      std_logic;
+       signal xmask_ce:        std_logic;
+       signal xmask_oe:        std_logic;
+       signal xmask_addr_h:    std_logic;
+       signal xmask_addr_l:    std_logic;
 
-       signal xmask_rp:      std_logic;
-       signal xmask_byte:    std_logic;
-       signal xmask_ce:      std_logic;
-       signal xmask_oe:      std_logic;
-       signal xmask_addr_h:  std_logic;
-       signal xmask_addr_l:  std_logic;
+       signal zmask_ce:        std_logic;
+       signal zmask_oe:        std_logic;
+       signal zmask_byte:      std_logic;
 
-       signal zmask_ce:      std_logic;
-       signal zmask_oe:      std_logic;
-       signal zmask_byte:    std_logic;
+       ----------------------------------------------------------------------------
+       -- Other registers
+
+       signal ecr_reg:         std_logic_vector(23 downto 0);
+       signal sts_config_reg:  std_logic_vector(7 downto 0);
+
+       ----------------------------------------------------------------------------
+       -- CUI state machine
+
+       type cui_state_t is (
+               C_IDLE,
+               C_PROG_STS,
+               C_PROG_OTP,
+               C_PROG_WORD,
+               C_PROG_BUF_COUNT,
+               C_PROG_BUF_DATA,
+               C_ERASE,
+               C_LOCK_OR_ECR
+       );
+
+       signal cui_state_cur:   cui_state_t;
+
+       ----------------------------------------------------------------------------
+       -- Write state machine
+
+       type wsm_state_t is (
+               W_IDLE,
+               W_PROG_OTP,
+               W_PROG_WORD,
+               W_PROG_WORD_FINISH,
+               W_PROG_BUF,
+               W_ERASE,
+               W_ERASE_FINISH,
+               W_LOCK,
+               W_UNLOCK
+       );
+
+       signal wsm_state_cur:   wsm_state_t;
+
+       signal trig_clrsts:     std_logic;
+       signal trig_susp:       std_logic;
+       signal trig_resume:     std_logic;
+       signal trig_cmderr:     std_logic;
+       signal trig_otp:        std_logic;
+       signal trig_word:       std_logic;
+       signal trig_buf:        std_logic;
+       signal trig_erase:      std_logic;
+       signal trig_lock:       std_logic;
+       signal trig_unlock:     std_logic;
+
+       signal prog_word:       std_logic_vector(15 downto 0);
+       signal prog_addr:       std_logic_vector(23 downto 0);
+       signal erase_addr:      std_logic_vector(23 downto 0);
+       signal lock_addr:       std_logic_vector(23 downto 0);
+       signal unlock_addr:     std_logic_vector(23 downto 0);
 
 begin
 
@@ -167,14 +244,49 @@ begin
                wait;
        end process;
 
-       array_word <= sparse_get(flash_array, to_integer(unsigned(a(a'high downto 1) & '0'))) &
-                     sparse_get(flash_array, to_integer(unsigned(a(a'high downto 1) & '1'))) after T_OH;
+       process (a, sts_ready)
+       begin
+               -- sts_ready is in the sensitivity list because flash_array is a variable and cannot be
+               array_word <= sparse_get(flash_array, to_integer(unsigned(a(a'high downto 1) & '0'))) &
+                             sparse_get(flash_array, to_integer(unsigned(a(a'high downto 1) & '1'))) after T_OH;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Device Information
+
+       id_word <= (others => 'X');
+
+
+       ----------------------------------------------------------------------------
+       -- Status Register
+
+       sts_word <= "00000000"      &
+                   sts_ready       &
+                   sts_susp_erase  &
+                   sts_error_erase &
+                   sts_error_prog  &
+                   sts_error_vpen  &
+                   sts_susp_prog   &
+                   sts_error_lock  &
+                               '0';
+
+
+       ----------------------------------------------------------------------------
+       -- CFI Query
+
+       cfi_word <= (others => 'X');
 
 
        ----------------------------------------------------------------------------
        -- Output value
 
-       word <= array_word;
+       with read_state_cur select word <=
+               array_word      when R_ARRAY,
+               id_word         when R_ID,
+               sts_word        when R_STATUS,
+               cfi_word        when R_CFI,
+               (others => 'X') when others;
 
        e_xmask_rp: entity work.changed_within_t
                generic map (T => T_PHQV)
@@ -220,6 +332,297 @@ begin
                          word_xz(15 downto 8);
 
 
+       ----------------------------------------------------------------------------
+       -- Command User Interface (CUI)
+
+       process (rp_n, internal_we_n, a, d)
+       begin
+               if rp_n = '0' then
+                       cui_state_cur <= C_IDLE;
+                       trig_clrsts   <= '0';
+                       trig_susp     <= '0';
+                       trig_resume   <= '0';
+                       trig_cmderr   <= '0';
+                       trig_otp      <= '0';
+                       trig_word     <= '0';
+                       trig_buf      <= '0';
+                       trig_erase    <= '0';
+                       trig_lock     <= '0';
+                       trig_unlock   <= '0';
+               elsif falling_edge(internal_we_n) then
+                       trig_clrsts <= '0';
+                       trig_susp   <= '0';
+                       trig_resume <= '0';
+                       trig_cmderr <= '0';
+                       trig_otp    <= '0';
+                       trig_word   <= '0';
+                       trig_buf    <= '0';
+                       trig_erase  <= '0';
+                       trig_lock   <= '0';
+                       trig_unlock <= '0';
+               elsif rising_edge(internal_we_n) then
+                       case cui_state_cur is
+                               when C_IDLE =>
+                                       case d(7 downto 0) is
+                                               when x"FF" =>  -- Read Array
+                                                       read_state_cur <= R_ARRAY;
+
+                                               when x"70" =>  -- Read Status Register
+                                                       read_state_cur <= R_STATUS;
+
+                                               when x"90" =>  -- Read Identifier Codes/Device Information
+                                                       report "TODO: Read identifier codes and device information" severity error;
+                                                       read_state_cur <= R_ID;
+
+                                               when x"98" =>  -- CFI Query
+                                                       report "TODO: CFI query" severity error;
+                                                       read_state_cur <= R_CFI;
+
+                                               when x"50" =>  -- Clear Status Register
+                                                       trig_clrsts <= '1';
+
+                                               when x"B8" =>  -- Program STS Configuration Register
+                                                       cui_state_cur <= C_PROG_STS;
+
+                                               when x"c0" =>  -- Program OTP Register
+                                                       cui_state_cur <= C_PROG_OTP;
+
+                                               when x"40" | x"10" =>  -- Word/Byte Program
+                                                       cui_state_cur <= C_PROG_WORD;
+
+                                               when x"E8" =>  -- Buffered Program
+                                                       read_state_cur <= R_STATUS;
+                                                       cui_state_cur  <= C_PROG_BUF_COUNT;
+
+                                               when x"20" =>  -- Block Erase
+                                                       cui_state_cur <= C_ERASE;
+
+                                               when x"60" =>  -- Lock/Unlock Block or Program Enhanced Configuration Register
+                                                       cui_state_cur <= C_LOCK_OR_ECR;
+
+                                               when x"B0" =>  -- Program/Erase Suspend
+                                                       trig_susp      <= '1';
+                                                       read_state_cur <= R_STATUS;
+
+                                               when x"D0" =>  -- Program/Erase Resume
+                                                       trig_resume    <= '1';
+                                                       read_state_cur <= R_STATUS;
+
+                                               when others =>
+                                                       trig_cmderr <= '1';
+                                       end case;
+
+                               when C_PROG_STS =>
+                                       assert d(7 downto 0) = x"00" report "TODO: STS pulse config" severity error;
+                                       sts_config_reg <= d(7 downto 0);
+                                       cui_state_cur  <= C_IDLE;
+
+                               when C_PROG_OTP =>
+                                       trig_otp       <= '1';
+                                       read_state_cur <= R_STATUS;
+                                       cui_state_cur  <= C_IDLE;
+
+                               when C_PROG_WORD =>
+                                       prog_word      <= d;
+                                       prog_addr      <= a;
+                                       trig_word      <= '1';
+                                       read_state_cur <= R_STATUS;
+                                       cui_state_cur  <= C_IDLE;
+
+                               when C_PROG_BUF_COUNT =>
+                                       report "TODO: buffered program" severity error;
+                                       cui_state_cur <= C_PROG_BUF_DATA;
+
+                               when C_PROG_BUF_DATA =>
+                                       cui_state_cur <= C_IDLE;
+
+                               when C_ERASE =>
+                                       case d(7 downto 0) is
+                                               when x"D0" =>  -- Erase Block
+                                                       erase_addr     <= a;
+                                                       trig_erase     <= '1';
+                                                       read_state_cur <= R_STATUS;
+                                                       cui_state_cur  <= C_IDLE;
+
+                                               when others =>
+                                                       trig_cmderr    <= '1';
+                                                       cui_state_cur  <= C_IDLE;
+                                       end case;
+
+                               when C_LOCK_OR_ECR =>
+                                       case d(7 downto 0) is
+                                               when x"04" =>  -- Program Enhanced Configuration Register
+                                                       assert a = x"000000" report "TODO: ECR configuration" severity error;
+                                                       ecr_reg       <= a;
+                                                       cui_state_cur <= C_IDLE;
+
+                                               when x"01" =>  -- Lock Block
+                                                       lock_addr      <= a;
+                                                       trig_lock      <= '1';
+                                                       read_state_cur <= R_STATUS;
+                                                       cui_state_cur  <= C_IDLE;
+
+                                               when x"0D" =>  -- Unlock block
+                                                       unlock_addr    <= a;
+                                                       trig_unlock    <= '1';
+                                                       read_state_cur <= R_STATUS;
+                                                       cui_state_cur  <= C_IDLE;
+
+                                               when others =>
+                                                       trig_cmderr   <= '1';
+                                                       cui_state_cur <= C_IDLE;
+                                       end case;
+
+                               when others =>
+                                       report "Unhandled CUI state" severity error;
+                       end case;
+               end if;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Write State Machine (WSM)
+
+       process (wsm_state_cur, rp_n, vpen,
+                trig_clrsts, trig_susp, trig_resume, trig_cmderr, trig_otp,
+                trig_word, trig_buf, trig_erase, trig_lock, trig_unlock)
+       begin
+               if rp_n = '0' then
+                       wsm_state_cur   <= W_IDLE;
+
+                       -- Clear all error and status bits and initialize to ready
+                       sts_ready       <= '1';
+                       sts_susp_erase  <= '0';
+                       sts_error_erase <= '0';
+                       sts_error_prog  <= '0';
+                       sts_error_vpen  <= '0';
+                       sts_susp_prog   <= '0';
+                       sts_error_lock  <= '0';
+               else
+                       -- Clearing error status bits should probably be allowed in any WSM state
+                       if rising_edge(trig_clrsts) then
+                               sts_error_erase <= '0';
+                               sts_error_prog  <= '0';
+                               sts_error_vpen  <= '0';
+                               sts_error_lock  <= '0';
+                       end if;
+
+                       -- Command errors should probably be latched in any WSM state
+                       if rising_edge(trig_cmderr) then
+                               sts_error_erase <= '1';
+                               sts_error_prog  <= '1';
+                       end if;
+
+                       -- Handle each state's logic
+                       -- Keep in mind this is not only run when wsm_state_cur changes,
+                       -- but also rerun when vpen or any trigger signal change
+                       sts_ready <= '0';
+                       case wsm_state_cur is
+                               when W_IDLE =>
+                                       sts_ready <= '1';
+
+                                       -- After these state transitions, this process will be rerun
+                                       -- in the next delta cycle with the new state
+                                       if rising_edge(trig_resume) then
+                                               report "TODO: resume program/erase operation" severity error;
+                                       elsif rising_edge(trig_otp) then
+                                               wsm_state_cur <= W_PROG_OTP;
+                                       elsif rising_edge(trig_word) then
+                                               wsm_state_cur <= W_PROG_WORD;
+                                       elsif rising_edge(trig_buf) then
+                                               wsm_state_cur <= W_PROG_BUF;
+                                       elsif rising_edge(trig_erase) then
+                                               wsm_state_cur <= W_ERASE;
+                                       elsif rising_edge(trig_lock) then
+                                               wsm_state_cur <= W_LOCK;
+                                       elsif rising_edge(trig_unlock) then
+                                               wsm_state_cur <= W_UNLOCK;
+                                       end if;
+
+                               when W_PROG_OTP =>
+                                       report "TODO: program OTP" severity error;
+                                       wsm_state_cur <= W_IDLE;
+
+                               when W_PROG_WORD =>
+                                       -- TODO: check lock bits
+
+                                       -- If vpen is low or drops during programming, halt with error
+                                       if vpen = '0' then
+                                               sts_error_prog <= '1';
+                                               sts_error_vpen <= '1';
+                                               wsm_state_cur  <= W_IDLE;
+                                       end if;
+
+                                       -- If suspend command is sent, pause programming
+                                       if rising_edge(trig_susp) then
+                                               report "TODO: program suspend" severity error;
+                                       end if;
+
+                                       -- Invalidate the data and schedule programming completion
+                                       if byte_n = '0' then
+                                               sparse_set(flash_array, to_integer(unsigned(prog_addr)), "XXXXXXXX");
+                                       else
+                                               sparse_set(flash_array, to_integer(unsigned(prog_addr(prog_addr'high downto 1) & '0')), "XXXXXXXX");
+                                               sparse_set(flash_array, to_integer(unsigned(prog_addr(prog_addr'high downto 1) & '1')), "XXXXXXXX");
+                                       end if;
+                                       wsm_state_cur <= W_PROG_WORD_FINISH after T_WHQV3;
+
+                               when W_PROG_WORD_FINISH =>
+                                       if byte_n = '0' then
+                                               sparse_set(flash_array, to_integer(unsigned(prog_addr)), prog_word(7 downto 0));
+                                       else
+                                               sparse_set(flash_array, to_integer(unsigned(prog_addr(prog_addr'high downto 1) & '0')), prog_word(15 downto 8));
+                                               sparse_set(flash_array, to_integer(unsigned(prog_addr(prog_addr'high downto 1) & '1')), prog_word( 7 downto 0));
+                                       end if;
+                                       wsm_state_cur <= W_IDLE;
+
+                               when W_PROG_BUF =>
+                                       report "TODO: buffered program" severity error;
+                                       wsm_state_cur <= W_IDLE;
+
+                               when W_ERASE =>
+                                       -- TODO: check lock bits
+
+                                       -- If vpen is low or drops during erase, halt with error
+                                       if vpen = '0' then
+                                               sts_error_erase <= '1';
+                                               sts_error_vpen  <= '1';
+                                               wsm_state_cur   <= W_IDLE;
+                                       end if;
+
+                                       -- If suspend command is sent, pause programming
+                                       if rising_edge(trig_susp) then
+                                               report "TODO: erase suspend" severity error;
+                                       end if;
+
+                                       -- Invalidate the data and schedule the erase completion
+                                       for i in 0 to 16#1ffff# loop
+                                               sparse_set(flash_array, to_integer(unsigned(erase_addr(erase_addr'high downto 16)) & to_unsigned(i, 17)), x"FF");
+                                       end loop;
+                                       wsm_state_cur <= W_ERASE_FINISH after T_WHQV4;
+
+                               when W_ERASE_FINISH =>
+                                       for i in 0 to 16#1ffff# loop
+                                               sparse_set(flash_array, to_integer(unsigned(erase_addr(erase_addr'high downto 16)) & to_unsigned(i, 17)), x"FF");
+                                       end loop;
+                                       wsm_state_cur <= W_IDLE;
+
+                               when W_LOCK =>
+                                       report "TODO: program lock bits" severity error;
+                                       wsm_state_cur <= W_IDLE;
+
+                               when W_UNLOCK =>
+                                       report "TODO: erase lock bits" severity error;
+                                       wsm_state_cur <= W_IDLE;
+
+                               when others =>
+                                       report "Unhandled WSM state" severity error;
+
+                       end case;
+               end if;
+       end process;
+
+
        ----------------------------------------------------------------------------
        -- Check for erroneous usages
 
diff --git a/libraries/simulated/sim_memory.vhd b/libraries/simulated/sim_memory.vhd
new file mode 100644 (file)
index 0000000..be851b2
--- /dev/null
@@ -0,0 +1,172 @@
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+
+library std;
+use std.textio.all;
+
+
+entity sim_memory is
+       generic (
+               FILENAME: string := ""
+       );
+       port (
+               we:      in    std_logic;
+               address: in    std_logic_vector(15 downto 0);
+               data:    inout std_logic_vector(7 downto 0)
+       );
+end sim_memory;
+
+
+architecture behavioral of sim_memory is
+
+       function str_endswith(str: string; suffix: string) return boolean is
+       begin
+               if str'length < suffix'length then
+                       return false;
+               else
+                       return str(str'right - (suffix'length - 1) to str'right) = suffix;
+               end if;
+       end function;
+
+
+       -----------------------------------------------------------------
+       -- Linked-list implementation of sparsely populated list of bytes
+
+       subtype byte_t is std_logic_vector(7 downto 0);
+       type byte_array_t is array(natural range <>) of byte_t;
+       type p_byte_array_t is access byte_array_t;
+       type item_t;
+       type p_item_t is access item_t;
+
+       type sparse_t is record
+               default:   byte_t;
+               page_size: natural;
+               first:     p_item_t;
+       end record;
+
+       type item_t is record
+               base:      integer;
+               data:      p_byte_array_t;
+               next_item: p_item_t;
+       end record;
+
+
+       ----------------------------
+       -- Create a new sparse array
+       function sparse_new(default: byte_t := (others => 'U'); page_size: natural := 4096) return sparse_t is
+       begin
+               return (
+                       default   => default,
+                       page_size => page_size,
+                       first     => null
+               );
+       end function;
+
+
+       ----------------------------------
+       -- Get a value from a sparse array
+       function sparse_get(sparse: sparse_t; idx: natural) return byte_t is
+               variable base: natural;
+               variable this: p_item_t;
+       begin
+               -- Find a page that contains idx
+               base := idx - (idx mod sparse.page_size);
+               this := sparse.first;
+               while this /= null loop
+                       if this.base = base then
+                               -- Retrieve the value and exit
+                               return this.data(idx mod sparse.page_size);
+                       end if;
+                       this := this.next_item;
+               end loop;
+
+               -- No page containing idx, return the default value
+               return sparse.default;
+       end function;
+
+
+       ------------------------------------
+       -- Set a value within a sparse array
+       procedure sparse_set(sparse: inout sparse_t; idx: natural; val: byte_t) is
+               variable base:     natural;
+               variable this:     p_item_t;
+               variable new_item: p_item_t;
+       begin
+               -- Find a page that contains idx
+               base := idx - (idx mod sparse.page_size);
+               this := sparse.first;
+               while this /= null loop
+                       if this.base = base then
+                               -- Write the value and exit
+                               this.data(idx mod sparse.page_size) := val;
+                               return;
+                       end if;
+                       this := this.next_item;
+               end loop;
+
+               -- No page found containing idx, create one and add it
+               new_item := new item_t;
+
+               new_item.base      := base;
+               new_item.data      := new byte_array_t(sparse.page_size-1 downto 0);--'(others => sparse.default);
+               new_item.next_item := sparse.first;
+
+               sparse.first := new_item;
+
+               for i in 0 to sparse.page_size-1 loop
+                       new_item.data(i) := sparse.default;
+               end loop;
+               new_item.data(idx mod sparse.page_size) := val;
+       end procedure;
+
+begin
+
+       p_reset: process
+               type char_file_t is file of character;
+               subtype ibyte_t is natural range 0 to 255;
+
+               file f: char_file_t;
+               variable fstatus: FILE_OPEN_STATUS;
+
+               variable i: natural;
+               variable c: character;
+               variable b: ibyte_t;
+               variable v: byte_t;
+
+               variable mem: sparse_t;
+       begin
+               mem := sparse_new;
+
+               -- Load data from file
+               if str_endswith(FILENAME, ".bin") then
+                       -- Raw binary file
+
+                       file_open(fstatus, f, FILENAME, READ_MODE);
+                       assert fstatus = OPEN_OK report "Failed to open file '" & FILENAME & "'" severity failure;
+
+                       i := 0;
+                       while not endfile(f) loop
+                               read(f, c);
+                               b := character'pos(c);
+                               v := std_logic_vector(to_unsigned(b, 8));
+                               sparse_set(mem, i, v);
+                               report "char " & natural'image(i) & " = " & natural'image(b) & "";
+                               i := i + 1;
+                       end loop;
+
+                       file_close(f);
+
+               elsif str_endswith(FILENAME, ".hex") then
+                       -- Intel HEX format
+                       assert false report "Intel HEX format not yet supported" severity failure;
+               else
+                       assert false report "Filename suffix not recognized: '" & FILENAME & "'" severity failure;
+               end if;
+               file_close(f);
+
+               report integer'image(to_integer(unsigned(sparse_get(mem, 6))));
+               wait;
+       end process;
+
+end behavioral;
diff --git a/libraries/simulated/tests/test_attrs.vhd b/libraries/simulated/tests/test_attrs.vhd
new file mode 100644 (file)
index 0000000..e651e3a
--- /dev/null
@@ -0,0 +1,75 @@
+library ieee;
+use ieee.std_logic_1164.all;
+
+
+entity test_attrs is
+end test_attrs;
+
+
+architecture behavior of test_attrs is
+
+       constant T: time := 10 ns;
+
+       signal sig:               std_logic;
+       signal sig_delayed:       std_logic;
+       signal sig_stable:        boolean;
+       signal sig_quiet:         boolean;
+       signal sig_last_event:    time;
+       signal sig_last_active:   time;
+       signal sig_last_event_2:  time;
+       signal sig_last_active_2: time;
+
+begin
+
+       test: process is
+       begin
+
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+
+               sig <= '0';
+
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+               wait for 30 ns;
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+
+               sig <= '1';
+
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+               wait for 30 ns;
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+
+               sig <= '1';
+
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+               wait for 30 ns;
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+
+               sig <= '0';
+
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+               wait for 30 ns;
+               sig_last_event_2  <= sig'last_event;
+               sig_last_active_2 <= sig'last_active;
+
+               wait;
+
+       end process;
+
+       sig_delayed     <= sig'delayed(T);
+       sig_stable      <= sig'stable(T);
+       sig_quiet       <= sig'quiet(T);
+
+       -- These don't work as expected!
+       -- This also applies to equivalent processes with sensitivity lists
+       sig_last_event  <= sig'last_event;
+       sig_last_active <= sig'last_active;
+
+end;
diff --git a/libraries/simulated/tests/test_sim_memory.vhd b/libraries/simulated/tests/test_sim_memory.vhd
new file mode 100644 (file)
index 0000000..b03758c
--- /dev/null
@@ -0,0 +1,28 @@
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+
+library work;
+use work.sim_utility.all;
+
+
+entity test_sim_memory is
+end test_sim_memory;
+
+
+architecture behavior of test_sim_memory is
+       shared variable mem: sparse_t;
+begin
+
+       p_test: process is
+       begin
+               mem := sparse_create;
+
+               sparse_load(mem, "/home/ryan/Dropbox/Projects/VHDL/libraries/simulated/tests/test.bin");
+               report integer'image(to_integer(unsigned(sparse_get(mem, 6))));
+
+               -- Done
+               wait;
+       end process;
+
+end;
index b8ce84c99e0cb07db9e54d2961c407c5cae74644..6cb24563ea4386c89c38c7af9675c93341b40b99 100644 (file)
@@ -27,6 +27,7 @@ begin
        begin
                -- Initial values and reset
                a      <= x"000000";
+               d      <= "ZZZZZZZZZZZZZZZZ";
                ce     <= "111";
                rp_n   <= '0';
                oe_n   <= '1';
@@ -36,6 +37,8 @@ begin
                wait for 10 ns;
                rp_n   <= '1';
                wait for 1 us;
+
+               -- Test a page read
                ce     <= "000";
                oe_n   <= '0';
                wait for 100 ns;
@@ -48,6 +51,49 @@ begin
                oe_n   <= '1';
                ce     <= "111";
 
+               wait for 100 ns;
+
+               -- Send the write-word command
+               a    <= x"000008";
+               d    <= x"0040";
+               ce   <= "000";
+               we_n <= '0';
+               wait for 80 ns;
+               we_n <= '1';
+               ce   <= "111";
+               wait for 35 ns;
+
+               -- Send the word to write
+               d    <= x"1234";
+               ce   <= "000";
+               we_n <= '0';
+               wait for 80 ns;
+               we_n <= '1';
+               ce   <= "111";
+               wait for 35 ns;
+
+               -- Wait for the write to complete
+               wait until sts /= '0';
+               wait for 50 ns;
+
+               -- Send the read-array command
+               d    <= x"00ff";
+               ce   <= "000";
+               we_n <= '0';
+               wait for 80 ns;
+               we_n <= '1';
+               ce   <= "111";
+               wait for 35 ns;
+
+               -- Read back the value we wrote
+               d    <= "ZZZZZZZZZZZZZZZZ";
+               ce   <= "000";
+               oe_n <= '0';
+               wait for 80 ns;
+               oe_n <= '1';
+               ce   <= "111";
+               wait for 35 ns;
+
                wait;
        end process;
 
index ae2a95459d5327f7abdb4b3eb64abc359f56e31d..303989f06b44a17fa4dd7d7d00286f345b0b9f37 100644 (file)
@@ -9,7 +9,7 @@ use ieee.numeric_std.all;
 entity fifo is
        generic (
                WIDTH: integer := 8;
-               COUNT: integer := 4
+               COUNT: integer := 16
        );
        port (
                -- Not a Wishbone bus, but can still use the global Wishbone SYSCON
@@ -35,84 +35,6 @@ end fifo;
 
 architecture behavioral of fifo is
 
-       type data_array_t is array(natural range <>) of std_logic_vector(WIDTH-1 downto 0);
-
-       signal data_array_reg:   data_array_t(COUNT-1 downto 0);
-       signal data_array_shift: std_logic;
-
-       signal index_reg:        unsigned(4 downto 0);
-       signal index_up:         std_logic;
-       signal index_down:       std_logic;
-
-       signal full:             std_logic;
-       signal empty:            std_logic;
-
-begin
-
-       -- Wishbone-like interface
-       process (h_stb_i, t_ack_i)
-       begin
-               index_down <= '0';
-               index_up   <= '0';
-
-               if h_stb_i = '1' and full = '0' then
-                       index_up  <= '1';
-               end if;
-               if t_ack_i = '1' and empty = '0' then
-                       index_down <= '1';
-               end if;
-       end process;
-
-       t_stb_o  <= not empty;
-       h_ack_o  <= not full;
-
-       is_empty <= empty;
-       is_full  <= full;
-
-
-       -- Shift register of values
-       -- Cannot have reset or parallel-load logic if it's to be inferred as a LUT-shift-register
-       process (clk_i, index_up, data_array_reg, h_dat_i)
-       begin
-               if rising_edge(clk_i) then
-                       if index_up = '1' then
-                               for i in COUNT-1 downto 1 loop
-                                       data_array_reg(i) <= data_array_reg(i-1);
-                               end loop;
-                               data_array_reg(0) <= h_dat_i;
-                       end if;
-               end if;
-       end process;
-
-       t_dat_o <= data_array_reg(to_integer(index_reg(3 downto 0)));
-
-
-       -- Index counter
-       process (rst_i, clk_i, index_reg)
-       begin
-               if rising_edge(clk_i) then
-                       if rst_i = '1' then
-                               index_reg <= "01111";
-                       else
-                               if index_up = '1' and index_down = '0' then
-                                       index_reg <= index_reg + 1;
-                               elsif index_up = '0' and index_down = '1' then
-                                       index_reg <= index_reg - 1;
-                               end if;
-                       end if;
-               end if;
-       end process;
-
-
-       -- Emptiness/fullness detector
-       empty <= not index_reg(4);
-       full  <= and_reduce(std_logic_vector(index_reg));
-
-end behavioral;
-
-
-architecture behavioral_old of fifo is
-
        type data_array is array(natural range <>) of std_logic_vector(WIDTH-1 downto 0);
 
        signal stall:          std_logic_vector(COUNT-1 downto 0);
@@ -172,4 +94,4 @@ begin
                end if;
        end process;
 
-end behavioral_old;
+end behavioral;
diff --git a/libraries/utility/multiclk_ram.vhd b/libraries/utility/multiclk_ram.vhd
new file mode 100644 (file)
index 0000000..1a6cddb
--- /dev/null
@@ -0,0 +1,33 @@
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+
+
+entity multiclk_ram is
+       generic (
+               A: integer := 4;  -- Address width
+               N: integer := 8;  -- Data width
+       );
+       port (
+               -- The "native" clock domain, where the RAM itself lives
+               -- Read-only, and reads are asynchronous (clk_a_i is needed for signal domain crossing, not access)
+               clk_a_i: in  std_logic;
+               adr_a_i: in  std_logic_vector(A-1 downto 0);
+               dat_a_o: out std_logic_vector(N-1 downto 0);
+
+               -- The "external" clock domain, where the operator lives
+               -- Read and write
+               clk_b_i: in  std_logic;
+               stb_b_i: in  std_logic;
+               we_b_i:  in  std_logic;
+               ack_b_o: out std_logic;
+               adr_b_i: in  std_logic_vector(A-1 downto 0);
+               dat_b_i: in  std_logic_vector(N-1 downto 0);
+               dat_b_o: out std_logic_vector(N-1 downto 0);
+       );
+end multiclk_ram;
+
+
+architecture behavioral of multiclk_ram is
+begin
+end behavioral;
diff --git a/libraries/utility/reg_file.vhd b/libraries/utility/reg_file.vhd
new file mode 100644 (file)
index 0000000..564d592
--- /dev/null
@@ -0,0 +1,57 @@
+--------------------------------------------------------------------------------
+-- reg_file - Generic register file
+--
+-- Port A - asynchronous read/synchronous write
+-- Port B - asynchronous read
+-- TODO: Verify that this is inferred as distributed RAM
+--------------------------------------------------------------------------------
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+use ieee.math_real.all;
+
+
+entity reg_file is
+       generic (
+               A: integer := 4;  -- Number of address bits
+               N: integer := 8   -- Number of data bits
+       );
+       port (
+               clk_a_i: in  std_logic;
+               we_a_i:  in  std_logic;
+               adr_a_i: in  std_logic_vector(A-1 downto 0);
+               dat_a_i: in  std_logic_vector(N-1 downto 0);
+               dat_a_o: in  std_logic_vector(N-1 downto 0);
+
+               adr_b_i: in  std_logic_vector(A-1 downto 0);
+               dat_b_o: out std_logic_vector(N-1 downto 0)
+       );
+end reg_file;
+
+
+architecture behavioral of reg_file is
+
+       constant MEM_SIZE: integer := 2**A;
+       type word_array_t is array(natural range <>) of std_logic_vector(N-1 downto 0);
+
+       signal file_reg: word_array_t(MEM_SIZE-1 downto 0);
+
+begin
+
+       -- Read-write port A
+       process (clk_a_i, we_a_i, adr_a_i, dat_a_i)
+       begin
+               if rising_edge(clk_a_i) then
+                       if we_a_i = '1' then
+                               file_reg(to_integer(unsigned(adr_a_i))) <= dat_a_i;
+                       end if;
+               end if;
+       end process;
+
+       dat_a_o <= file_reg(to_integer(unsigned(adr_a_i)));
+
+       -- Read-only port B
+       dat_b_o <= file_reg(to_integer(unsigned(adr_b_i)));
+
+end behavioral;
diff --git a/libraries/utility/reg_file_1w2r.vhd b/libraries/utility/reg_file_1w2r.vhd
new file mode 100644 (file)
index 0000000..2a26305
--- /dev/null
@@ -0,0 +1,60 @@
+--------------------------------------------------------------------------------
+-- reg_file - Generic register file
+--
+-- Port A - synchronous write
+-- Port B - asynchronous read
+-- Port C - asynchronous read
+--------------------------------------------------------------------------------
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.numeric_std.all;
+use ieee.math_real.all;
+
+
+entity reg_file_1w2r is
+       generic (
+               A: integer := 4;  -- Number of address bits
+               N: integer := 8   -- Number of data bits
+       );
+       port (
+               clk_a_i: in  std_logic;
+               we_a_i:  in  std_logic;
+               adr_a_i: in  std_logic_vector(A-1 downto 0);
+               dat_a_i: in  std_logic_vector(N-1 downto 0);
+
+               adr_b_i: in  std_logic_vector(A-1 downto 0);
+               dat_b_o: out std_logic_vector(N-1 downto 0);
+
+               adr_c_i: in  std_logic_vector(A-1 downto 0);
+               dat_c_o: out std_logic_vector(N-1 downto 0)
+       );
+end reg_file_1w2r;
+
+
+architecture behavioral of reg_file_1w2r is
+
+       constant MEM_SIZE: integer := 2**A;
+       type word_array_t is array(natural range <>) of std_logic_vector(N-1 downto 0);
+
+       signal file_reg: word_array_t(MEM_SIZE-1 downto 0);
+
+begin
+
+       -- Write-only port A
+       process (clk_a_i, we_a_i, adr_a_i, dat_a_i)
+       begin
+               if rising_edge(clk_a_i) then
+                       if we_a_i = '1' then
+                               file_reg(to_integer(unsigned(adr_a_i))) <= dat_a_i;
+                       end if;
+               end if;
+       end process;
+
+       -- Read-only port B
+       dat_b_o <= file_reg(to_integer(unsigned(adr_b_i)));
+
+       -- Read-only port C
+       dat_c_o <= file_reg(to_integer(unsigned(adr_c_i)));
+
+end behavioral;
index 52225c065f542b575bc6ec218977d9f112b2fceb..6fb6bf5a76b7432938186127692df8757ce77dac 100644 (file)
@@ -1,14 +1,67 @@
 --------------------------------------------------------------------------------
 -- vga_tiler - tile-based graphics controller for VGA interfaces
 --------------------------------------------------------------------------------
--- 0x0000 - 0x2000: Screen buffer
---                  Each byte is an index into tile memory
+-- 0x0000 - 0x3fff: Screen buffer
+--                  Each byte pair is an index into tile memory and color
 --                  Byte 0 is the top-left tile
--- 0x2000 - 0x27ff: Tile data
+-- 0x4000 - 0x47ff: Tile data
 --                  Each tile is 8x8 pixels and consists of 8 bytes
 --                  The first byte of a tile is the top row, one pixel per bit
 --                  At startup, a subset of the Commodore64 font is loaded into
 --                  tile memory, mapped to appropriate ASCII characters
+--
+--       +---+---+---+---+---+---+---+---+
+--       | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
+--       +---+---+---+---+---+---+---+---+
+-- 0x00  |     R     |     G     |   B   | COL_0
+--       +-----------+-----------+-------+
+-- 0x01  |     R     |     G     |   B   | COL_1
+--       +-----------+-----------+-------+
+-- 0x02  |     R     |     G     |   B   | COL_2
+--       +-----------+-----------+-------+
+-- 0x03  |     R     |     G     |   B   | COL_3
+--       +-----------+-----------+-------+
+-- 0x04  |     R     |     G     |   B   | COL_4
+--       +-----------+-----------+-------+
+-- 0x05  |     R     |     G     |   B   | COL_5
+--       +-----------+-----------+-------+
+-- 0x06  |     R     |     G     |   B   | COL_6
+--       +-----------+-----------+-------+
+-- 0x07  |     R     |     G     |   B   | COL_7
+--       +-----------+-----------+-------+
+-- 0x08  |     R     |     G     |   B   | COL_8
+--       +-----------+-----------+-------+
+-- 0x09  |     R     |     G     |   B   | COL_9
+--       +-----------+-----------+-------+
+-- 0x0a  |     R     |     G     |   B   | COL_A
+--       +-----------+-----------+-------+
+-- 0x0b  |     R     |     G     |   B   | COL_B
+--       +-----------+-----------+-------+
+-- 0x0c  |     R     |     G     |   B   | COL_C
+--       +-----------+-----------+-------+
+-- 0x0d  |     R     |     G     |   B   | COL_D
+--       +-----------+-----------+-------+
+-- 0x0e  |     R     |     G     |   B   | COL_E
+--       +-----------+-----------+-------+
+-- 0x0f  |     R     |     G     |   B   | COL_F
+--       +-----------+-----------+-------+
+-- 0x10  |            START_L            |
+--       +-------------------------------+
+-- 0x11  |            START_H            |
+--       +-------+-----------+-----------+
+-- 0x12  |       |   OFF_Y   |   OFF_X   | OFFSET
+--       +-------+-----------+-----------+
+--
+-- COL_N:
+-- R/G/B color values for each of 16 palette colors
+--
+-- START_L/H: (TODO)
+-- Offset within screen buffer where tile (0, 0) should be read from
+-- Treated as a 16-bit-word address (only addresses even address within buffer)
+--
+-- OFF_X/Y: (TODO)
+-- Pixel offsets to apply when drawing tiles
+--
 --------------------------------------------------------------------------------
 -- WISHBONE DATASHEET
 --
 -- Operand sizes: 8-bit
 -- Endianness: undefined (port size same as granularity)
 -- Data transfer sequence: undefined
--- Clock constraints: 50 MHz expected
+-- Clock constraints: none
 -- Signals:
 -- * rst_i
 -- * clk_i
--- * cyc_i
+-- * scr_cyc_i  (CYC_I for screen buffer)
+-- * tile_cyc_i (CYC_I for tile bitmaps)
+-- * pal_cyc_i  (CYC_I for RO palette registers)
 -- * stb_i
 -- * we_i
 -- * ack_o
@@ -39,30 +94,37 @@ use ieee.numeric_std.all;
 library unisim;
 use unisim.vcomponents.all;
 
+library utility;
+
 library work;
 
 
 entity vga_tiler is
        port (
                -- Wishbone SYSCON
-               rst_i:    in  std_logic;
-               clk_i:    in  std_logic;  -- 50MHz
+               rst_i:      in  std_logic;
+               clk_i:      in  std_logic;
 
                -- System access to video ram
-               cyc_i:    in  std_logic;
-               stb_i:    in  std_logic;
-               we_i:     in  std_logic;
-               ack_o:    out std_logic;
-               adr_i:    in  std_logic_vector(13 downto 0);
-               dat_i:    in  std_logic_vector(7 downto 0);
-               dat_o:    out std_logic_vector(7 downto 0);
+               scr_cyc_i:  in  std_logic;
+               tile_cyc_i: in  std_logic;
+               pal_cyc_i:  in  std_logic;
+               stb_i:      in  std_logic;
+               we_i:       in  std_logic;
+               ack_o:      out std_logic;
+               adr_i:      in  std_logic_vector(13 downto 0);
+               dat_i:      in  std_logic_vector(7 downto 0);
+               dat_o:      out std_logic_vector(7 downto 0);
+
+               -- VGA config
+               vga_clk:    in  std_logic;  -- 50 MHz
 
                -- VGA output
-               vgaRed:   out std_logic_vector(3 downto 1);
-               vgaGreen: out std_logic_vector(3 downto 1);
-               vgaBlue:  out std_logic_vector(3 downto 2);
-               Hsync:    out std_logic;
-               Vsync:    out std_logic
+               vgaRed:     out std_logic_vector(3 downto 1);
+               vgaGreen:   out std_logic_vector(3 downto 1);
+               vgaBlue:    out std_logic_vector(3 downto 2);
+               Hsync:      out std_logic;
+               Vsync:      out std_logic
        );
 end vga_tiler;
 
@@ -77,11 +139,20 @@ architecture behavioral of vga_tiler is
        signal char1_stb_i:        std_logic;
        signal char2_stb_i:        std_logic;
        signal char3_stb_i:        std_logic;
+       signal char4_stb_i:        std_logic;
+       signal char5_stb_i:        std_logic;
+       signal char6_stb_i:        std_logic;
+       signal char7_stb_i:        std_logic;
        signal tile_stb_i:         std_logic;
+       signal palette_we:         std_logic;
        signal char0_dat_o:        std_logic_vector(7 downto 0);
        signal char1_dat_o:        std_logic_vector(7 downto 0);
        signal char2_dat_o:        std_logic_vector(7 downto 0);
        signal char3_dat_o:        std_logic_vector(7 downto 0);
+       signal char4_dat_o:        std_logic_vector(7 downto 0);
+       signal char5_dat_o:        std_logic_vector(7 downto 0);
+       signal char6_dat_o:        std_logic_vector(7 downto 0);
+       signal char7_dat_o:        std_logic_vector(7 downto 0);
        signal tile_dat_o:         std_logic_vector(7 downto 0);
 
        -- BRAM is faster than the external ram, and is dual-ported to prevent bus
@@ -130,13 +201,19 @@ architecture behavioral of vga_tiler is
        signal s12_pix_x_reg:      std_logic_vector(10 downto 0);
        signal s12_pix_y_reg:      std_logic_vector(9 downto 0);
        signal s12_char_idx_reg:   unsigned(12 downto 0);
-       signal s12_bank0_char_reg: std_logic_vector(7 downto 0);
-       signal s12_bank1_char_reg: std_logic_vector(7 downto 0);
-       signal s12_bank2_char_reg: std_logic_vector(7 downto 0);
-       signal s12_bank3_char_reg: std_logic_vector(7 downto 0);
+       signal s12_bank0_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank1_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank2_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank3_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank4_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank5_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank6_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank7_char_reg: std_logic_vector(15 downto 0);
 
        -- Stage 2: Select the tile ID from the correct bank and compute tile location within tile ram
+       signal s2_charcol:         std_logic_vector(15 downto 0);
        signal s2_char:            std_logic_vector(7 downto 0);
+       signal s2_color:           std_logic_vector(7 downto 0);
        signal s2_tile_idx:        std_logic_vector(10 downto 0);
 
        -- Register 2-3
@@ -147,8 +224,13 @@ architecture behavioral of vga_tiler is
        signal s23_pix_x_reg:      std_logic_vector(10 downto 0);
        signal s23_pix_y_reg:      std_logic_vector(9 downto 0);
        signal s23_tile_idx_reg:   std_logic_vector(10 downto 0);
+       signal s23_color_reg:      std_logic_vector(7 downto 0);
 
-       -- Stage 3: Lookup tile slice within tile ram
+       -- Stage 3: Lookup tile slice within tile ram and colors in palette
+       signal s3_fg_palette_adr:  std_logic_vector(3 downto 0);
+       signal s3_bg_palette_adr:  std_logic_vector(3 downto 0);
+       signal s3_fg_color:        std_logic_vector(7 downto 0);
+       signal s3_bg_color:        std_logic_vector(7 downto 0);
 
        -- Register 3-4
        signal s34_h_sync_reg:     std_logic;
@@ -157,6 +239,8 @@ architecture behavioral of vga_tiler is
        signal s34_v_blank_reg:    std_logic;
        signal s34_pix_x_reg:      std_logic_vector(10 downto 0);
        signal s34_pix_y_reg:      std_logic_vector(9 downto 0);
+       signal s34_fg_color_reg:   std_logic_vector(7 downto 0);
+       signal s34_bg_color_reg:   std_logic_vector(7 downto 0);
        signal s34_tile_line_reg:  std_logic_vector(7 downto 0);
 
        -- Stage 4: Select bit within tile slice an map to color
@@ -177,7 +261,7 @@ begin
 
        ----------------------------------------------------------------------------
        -- System Wishbone interface
-       -- FIXME: this may do double reads/writes - not a problem for now though
+       -- FIXME: this may do double writes - not a problem for now though
 
 
        process (rst_i, clk_i, wb_state_next)
@@ -211,19 +295,28 @@ begin
                end case;
        end process;
 
-       with adr_i(13 downto 11) select dat_o <=
-               char0_dat_o     when "000",
-               char1_dat_o     when "001",
-               char2_dat_o     when "010",
-               char3_dat_o     when "011",
-               tile_dat_o      when "100",
+       with tile_cyc_i & scr_cyc_i & adr_i(13 downto 11) select dat_o <=
+               char0_dat_o     when "01000",
+               char1_dat_o     when "01001",
+               char2_dat_o     when "01010",
+               char3_dat_o     when "01011",
+               char4_dat_o     when "01100",
+               char5_dat_o     when "01101",
+               char6_dat_o     when "01110",
+               char7_dat_o     when "01111",
+               tile_dat_o      when "10---",
                (others => '1') when others;
 
-       char0_stb_i <= stb_i and cyc_i when adr_i(13 downto 11) = "000" else '0';
-       char1_stb_i <= stb_i and cyc_i when adr_i(13 downto 11) = "001" else '0';
-       char2_stb_i <= stb_i and cyc_i when adr_i(13 downto 11) = "010" else '0';
-       char3_stb_i <= stb_i and cyc_i when adr_i(13 downto 11) = "011" else '0';
-       tile_stb_i  <= stb_i and cyc_i when adr_i(13 downto 11) = "100" else '0';
+       char0_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "000" else '0';
+       char1_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "001" else '0';
+       char2_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "010" else '0';
+       char3_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "011" else '0';
+       char4_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "100" else '0';
+       char5_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "101" else '0';
+       char6_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "110" else '0';
+       char7_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "111" else '0';
+       tile_stb_i  <= tile_cyc_i and stb_i;
+       palette_we  <= pal_cyc_i  and stb_i and we_i;
 
 
        ----------------------------------------------------------------------------
@@ -231,7 +324,7 @@ begin
 
        e_vga_counter: entity work.vga_counter
                port map (
-                       clk_50  => clk_i,
+                       clk_50  => vga_clk,
 
                        pix_x   => s0_pix_x,
                        pix_y   => s0_pix_y,
@@ -258,9 +351,9 @@ begin
 
 
        -- Register 0-1
-       process (clk_i, s0_h_sync, s0_v_sync, s0_h_blank, s0_v_blank, s0_pix_x, s0_pix_y, s0_char_idx)
+       process (vga_clk, s0_h_sync, s0_v_sync, s0_h_blank, s0_v_blank, s0_pix_x, s0_pix_y, s0_char_idx)
        begin
-               if rising_edge(clk_i) then
+               if rising_edge(vga_clk) then
                        s01_h_sync_reg   <= s0_h_sync;
                        s01_v_sync_reg   <= s0_v_sync;
                        s01_h_blank_reg  <= s0_h_blank;
@@ -276,7 +369,7 @@ begin
        -- Stage 1: Look up screen character's tile ID within screen buffer
 
 
-       e_char_bank_0: ramb16_s9_s9
+       e_char_bank_0: ramb16_s9_s18
                generic map (
                        INIT_00 => x"1f1e1d1c1b1a191817161514131211100f0e0d0c0b0a09080706050403020100",
                        INIT_01 => x"3f3e3d3c3b3a393837363534333231302f2e2d2c2b2a29282726252423222120",
@@ -288,117 +381,225 @@ begin
                        INIT_07 => x"fffefdfcfbfaf9f8f7f6f5f4f3f2f1f0efeeedecebeae9e8e7e6e5e4e3e2e1e0"
                )
                port map (
-                       -- Port A, tiler access
+                       -- Port A, 8-bit system access
                        ssra  => rst_i,
                        clka  => clk_i,
-                       ena   => '1',
-                       wea   => '0',
-                       addra => std_logic_vector(s01_char_idx_reg(10 downto 0)),
+                       ena   => char0_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
 
-                       doa   => s12_bank0_char_reg,
+                       doa   => char0_dat_o,
                        dopa  => open,
-                       dia   => (others => '0'),
+                       dia   => dat_i,
                        dipa  => "0",
 
-                       -- Port B, system access
+                       -- Port B, 16-bit tiler access
                        ssrb  => rst_i,
-                       clkb  => clk_i,
-                       enb   => char0_stb_i,
-                       web   => we_i,
-                       addrb => adr_i(10 downto 0),
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s01_char_idx_reg(9 downto 0)),
 
-                       dob   => char0_dat_o,
+                       dob   => s12_bank0_char_reg,
                        dopb  => open,
-                       dib   => dat_i,
-                       dipb  => "0"
+                       dib   => (others => '0'),
+                       dipb  => "00"
                );
 
-       e_char_bank_1: ramb16_s9_s9
+       e_char_bank_1: ramb16_s9_s18
                port map (
-                       -- Port A, tiler access
+                       -- Port A, 8-bit system access
                        ssra  => rst_i,
                        clka  => clk_i,
-                       ena   => '1',
-                       wea   => '0',
-                       addra => std_logic_vector(s01_char_idx_reg(10 downto 0)),
+                       ena   => char1_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
 
-                       doa   => s12_bank1_char_reg,
+                       doa   => char1_dat_o,
                        dopa  => open,
-                       dia   => (others => '0'),
+                       dia   => dat_i,
                        dipa  => "0",
 
-                       -- Port B, system access
+                       -- Port B, 16-bit tiler access
                        ssrb  => rst_i,
-                       clkb  => clk_i,
-                       enb   => char1_stb_i,
-                       web   => we_i,
-                       addrb => adr_i(10 downto 0),
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s01_char_idx_reg(9 downto 0)),
 
-                       dob   => char1_dat_o,
+                       dob   => s12_bank1_char_reg,
                        dopb  => open,
-                       dib   => dat_i,
-                       dipb  => "0"
+                       dib   => (others => '0'),
+                       dipb  => "00"
                );
 
-       e_char_bank_2: ramb16_s9_s9
+       e_char_bank_2: ramb16_s9_s18
                port map (
-                       -- Port A, tiler access
+                       -- Port A, 8-bit system access
                        ssra  => rst_i,
                        clka  => clk_i,
-                       ena   => '1',
-                       wea   => '0',
-                       addra => std_logic_vector(s01_char_idx_reg(10 downto 0)),
+                       ena   => char2_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
 
-                       doa   => s12_bank2_char_reg,
+                       doa   => char2_dat_o,
                        dopa  => open,
-                       dia   => (others => '0'),
+                       dia   => dat_i,
                        dipa  => "0",
 
-                       -- Port B, system access
+                       -- Port B, 16-bit tiler access
                        ssrb  => rst_i,
-                       clkb  => clk_i,
-                       enb   => char2_stb_i,
-                       web   => we_i,
-                       addrb => adr_i(10 downto 0),
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s01_char_idx_reg(9 downto 0)),
 
-                       dob   => char2_dat_o,
+                       dob   => s12_bank2_char_reg,
                        dopb  => open,
-                       dib   => dat_i,
-                       dipb  => "0"
+                       dib   => (others => '0'),
+                       dipb  => "00"
                );
 
-       e_char_bank_3: ramb16_s9_s9
+       e_char_bank_3: ramb16_s9_s18
                port map (
-                       -- Port A, tiler access
+                       -- Port A, 8-bit system access
                        ssra  => rst_i,
                        clka  => clk_i,
-                       ena   => '1',
-                       wea   => '0',
-                       addra => std_logic_vector(s01_char_idx_reg(10 downto 0)),
+                       ena   => char3_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
 
-                       doa   => s12_bank3_char_reg,
+                       doa   => char3_dat_o,
                        dopa  => open,
-                       dia   => (others => '0'),
+                       dia   => dat_i,
                        dipa  => "0",
 
-                       -- Port B, system access
+                       -- Port B, 16-bit tiler access
                        ssrb  => rst_i,
-                       clkb  => clk_i,
-                       enb   => char3_stb_i,
-                       web   => we_i,
-                       addrb => adr_i(10 downto 0),
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s01_char_idx_reg(9 downto 0)),
 
-                       dob   => char3_dat_o,
+                       dob   => s12_bank3_char_reg,
                        dopb  => open,
-                       dib   => dat_i,
-                       dipb  => "0"
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_4: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char4_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char4_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s01_char_idx_reg(9 downto 0)),
+
+                       dob   => s12_bank4_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_5: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char5_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char5_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s01_char_idx_reg(9 downto 0)),
+
+                       dob   => s12_bank5_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_6: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char6_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char6_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s01_char_idx_reg(9 downto 0)),
+
+                       dob   => s12_bank6_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_7: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char7_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char7_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s01_char_idx_reg(9 downto 0)),
+
+                       dob   => s12_bank7_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
                );
 
 
        -- Register 1-2
-       process (clk_i, s01_h_sync_reg, s01_v_sync_reg, s01_h_blank_reg, s01_v_blank_reg, s01_pix_x_reg, s01_pix_y_reg, s01_char_idx_reg)
+       process (vga_clk, s01_h_sync_reg, s01_v_sync_reg, s01_h_blank_reg, s01_v_blank_reg, s01_pix_x_reg, s01_pix_y_reg, s01_char_idx_reg)
        begin
-               if rising_edge(clk_i) then
+               if rising_edge(vga_clk) then
                        s12_h_sync_reg   <= s01_h_sync_reg;
                        s12_v_sync_reg   <= s01_v_sync_reg;
                        s12_h_blank_reg  <= s01_h_blank_reg;
@@ -410,6 +611,10 @@ begin
                        -- s12_bank1_char_reg
                        -- s12_bank2_char_reg
                        -- s12_bank3_char_reg
+                       -- s12_bank4_char_reg
+                       -- s12_bank5_char_reg
+                       -- s12_bank6_char_reg
+                       -- s12_bank7_char_reg
                end if;
        end process;
 
@@ -418,20 +623,26 @@ begin
        -- Stage 2: Select the tile ID from the correct bank and compute tile location within tile ram
 
 
-       with s12_char_idx_reg(12 downto 11) select s2_char <=
-               s12_bank0_char_reg when "00",
-               s12_bank1_char_reg when "01",
-               s12_bank2_char_reg when "10",
-               s12_bank3_char_reg when "11",
+       with s12_char_idx_reg(12 downto 10) select s2_charcol <=
+               s12_bank0_char_reg when "000",
+               s12_bank1_char_reg when "001",
+               s12_bank2_char_reg when "010",
+               s12_bank3_char_reg when "011",
+               s12_bank4_char_reg when "100",
+               s12_bank5_char_reg when "101",
+               s12_bank6_char_reg when "110",
+               s12_bank7_char_reg when "111",
                (others => 'X')    when others;
 
+       s2_char     <= s2_charcol( 7 downto 0);
+       s2_color    <= s2_charcol(15 downto 8);
        s2_tile_idx <= s2_char & s12_pix_y_reg(2 downto 0);
 
 
        -- Register 2-3
-       process (clk_i, s12_h_sync_reg, s12_v_sync_reg, s12_h_blank_reg, s12_v_blank_reg, s12_pix_x_reg, s12_pix_y_reg, s2_tile_idx)
+       process (vga_clk, s12_h_sync_reg, s12_v_sync_reg, s12_h_blank_reg, s12_v_blank_reg, s12_pix_x_reg, s12_pix_y_reg, s2_tile_idx)
        begin
-               if rising_edge(clk_i) then
+               if rising_edge(vga_clk) then
                        s23_h_sync_reg   <= s12_h_sync_reg;
                        s23_v_sync_reg   <= s12_v_sync_reg;
                        s23_h_blank_reg  <= s12_h_blank_reg;
@@ -439,12 +650,13 @@ begin
                        s23_pix_x_reg    <= s12_pix_x_reg;
                        s23_pix_y_reg    <= s12_pix_y_reg;
                        s23_tile_idx_reg <= s2_tile_idx;
+                       s23_color_reg    <= s2_color;
                end if;
        end process;
 
 
        ----------------------------------------------------------------------------
-       -- Stage 3: Lookup tile slice within tile ram
+       -- Stage 3: Lookup tile slice within tile ram and colors from palette
 
 
        e_tile_ram: ramb16_s9_s9
@@ -476,7 +688,7 @@ begin
                port map (
                        -- Port A, tiler access
                        ssra  => rst_i,
-                       clka  => clk_i,
+                       clka  => vga_clk,
                        ena   => '1',
                        wea   => '0',
                        addra => s23_tile_idx_reg,
@@ -499,17 +711,40 @@ begin
                        dipb  => "0"
                );
 
+       -- Palette reads are asynchronous and writes should only happen during
+       -- blanking intervals, so it's probably fine to have writes happen in a
+       -- different clock domain
+       e_palette: entity utility.reg_file_1w2r
+               generic map (A => 4, N => 8)
+               port map (
+                       clk_a_i => clk_i,
+                       we_a_i  => palette_we,
+                       adr_a_i => adr_i(3 downto 0),
+                       dat_a_i => dat_i,
+
+                       adr_b_i => s3_fg_palette_adr,
+                       dat_b_o => s3_fg_color,
+
+                       adr_c_i => s3_bg_palette_adr,
+                       dat_c_o => s3_bg_color
+               );
+
+       s3_fg_palette_adr <= s23_color_reg(3 downto 0);
+       s3_bg_palette_adr <= s23_color_reg(7 downto 4);
+
 
        -- Register 3-4
-       process (clk_i, s23_h_sync_reg, s23_v_sync_reg, s23_h_blank_reg, s23_v_blank_reg, s23_pix_x_reg, s23_pix_y_reg)
+       process (vga_clk, s23_h_sync_reg, s23_v_sync_reg, s23_h_blank_reg, s23_v_blank_reg, s23_pix_x_reg, s23_pix_y_reg)
        begin
-               if rising_edge(clk_i) then
-                       s34_h_sync_reg  <= s23_h_sync_reg;
-                       s34_v_sync_reg  <= s23_v_sync_reg;
-                       s34_h_blank_reg <= s23_h_blank_reg;
-                       s34_v_blank_reg <= s23_v_blank_reg;
-                       s34_pix_x_reg   <= s23_pix_x_reg;
-                       s34_pix_y_reg   <= s23_pix_y_reg;
+               if rising_edge(vga_clk) then
+                       s34_h_sync_reg   <= s23_h_sync_reg;
+                       s34_v_sync_reg   <= s23_v_sync_reg;
+                       s34_h_blank_reg  <= s23_h_blank_reg;
+                       s34_v_blank_reg  <= s23_v_blank_reg;
+                       s34_pix_x_reg    <= s23_pix_x_reg;
+                       s34_pix_y_reg    <= s23_pix_y_reg;
+                       s34_fg_color_reg <= s3_fg_color;
+                       s34_bg_color_reg <= s3_bg_color;
                        -- s34_tile_line_reg
                end if;
        end process;
@@ -519,28 +754,21 @@ begin
        -- Stage 4: Select bit within tile slice an map to color
 
 
-       --with s34_pix_x_reg(3 downto 1) select s4_bit <=
-       --      s34_tile_line_reg(7) when "000",
-       --      s34_tile_line_reg(6) when "001",
-       --      s34_tile_line_reg(5) when "010",
-       --      s34_tile_line_reg(4) when "011",
-       --      s34_tile_line_reg(3) when "100",
-       --      s34_tile_line_reg(2) when "101",
-       --      s34_tile_line_reg(1) when "110",
-       --      s34_tile_line_reg(0) when others;
-
        s4_bit       <= s34_tile_line_reg(to_integer(unsigned(not s34_pix_x_reg(3 downto 1))));
        s4_visible   <= not (s34_h_blank_reg or s34_v_blank_reg);
 
-       s4_vga_red   <= "111" when (s4_visible and s4_bit) = '1' else "000";
-       s4_vga_green <= "111" when (s4_visible and s4_bit) = '1' else "000";
-       s4_vga_blue  <= "11"  when (s4_visible and s4_bit) = '1' else "00";
+       -- s4_vga_red   <= "111" when (s4_visible and s4_bit) = '1' else "000";
+       -- s4_vga_green <= "111" when (s4_visible and s4_bit) = '1' else "000";
+       -- s4_vga_blue  <= "11"  when (s4_visible and s4_bit) = '1' else "00";
+       s4_vga_red   <= s34_fg_color_reg(7 downto 5) when (s4_visible and s4_bit) = '1' else s34_bg_color_reg(7 downto 5);
+       s4_vga_green <= s34_fg_color_reg(4 downto 2) when (s4_visible and s4_bit) = '1' else s34_bg_color_reg(4 downto 2);
+       s4_vga_blue  <= s34_fg_color_reg(1 downto 0) when (s4_visible and s4_bit) = '1' else s34_bg_color_reg(1 downto 0);
 
 
        -- Register 4-output
-       process (clk_i, s34_h_sync_reg, s34_v_sync_reg, s4_vga_red, s4_vga_green, s4_vga_blue)
+       process (vga_clk, s34_h_sync_reg, s34_v_sync_reg, s4_vga_red, s4_vga_green, s4_vga_blue)
        begin
-               if rising_edge(clk_i) then
+               if rising_edge(vga_clk) then
                        s4o_h_sync_reg    <= s34_h_sync_reg;
                        s4o_v_sync_reg    <= s34_v_sync_reg;
                        s4o_vga_red_reg   <= s4_vga_red;
diff --git a/libraries/vga/vga_tiler_opt.vhd b/libraries/vga/vga_tiler_opt.vhd
new file mode 100644 (file)
index 0000000..de1d825
--- /dev/null
@@ -0,0 +1,791 @@
+--------------------------------------------------------------------------------
+-- vga_tiler - tile-based graphics controller for VGA interfaces
+--------------------------------------------------------------------------------
+-- 0x0000 - 0x3fff: Screen buffer
+--                  Each byte pair is an index into tile memory and color
+--                  Byte 0 is the top-left tile
+-- 0x4000 - 0x47ff: Tile data
+--                  Each tile is 8x8 pixels and consists of 8 bytes
+--                  The first byte of a tile is the top row, one pixel per bit
+--                  At startup, a subset of the Commodore64 font is loaded into
+--                  tile memory, mapped to appropriate ASCII characters
+--
+--       +---+---+---+---+---+---+---+---+
+--       | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
+--       +---+---+---+---+---+---+---+---+
+-- 0x00  |     R     |     G     |   B   | COL_0
+--       +-----------+-----------+-------+
+-- 0x01  |     R     |     G     |   B   | COL_1
+--       +-----------+-----------+-------+
+-- 0x02  |     R     |     G     |   B   | COL_2
+--       +-----------+-----------+-------+
+-- 0x03  |     R     |     G     |   B   | COL_3
+--       +-----------+-----------+-------+
+-- 0x04  |     R     |     G     |   B   | COL_4
+--       +-----------+-----------+-------+
+-- 0x05  |     R     |     G     |   B   | COL_5
+--       +-----------+-----------+-------+
+-- 0x06  |     R     |     G     |   B   | COL_6
+--       +-----------+-----------+-------+
+-- 0x07  |     R     |     G     |   B   | COL_7
+--       +-----------+-----------+-------+
+-- 0x08  |     R     |     G     |   B   | COL_8
+--       +-----------+-----------+-------+
+-- 0x09  |     R     |     G     |   B   | COL_9
+--       +-----------+-----------+-------+
+-- 0x0a  |     R     |     G     |   B   | COL_A
+--       +-----------+-----------+-------+
+-- 0x0b  |     R     |     G     |   B   | COL_B
+--       +-----------+-----------+-------+
+-- 0x0c  |     R     |     G     |   B   | COL_C
+--       +-----------+-----------+-------+
+-- 0x0d  |     R     |     G     |   B   | COL_D
+--       +-----------+-----------+-------+
+-- 0x0e  |     R     |     G     |   B   | COL_E
+--       +-----------+-----------+-------+
+-- 0x0f  |     R     |     G     |   B   | COL_F
+--       +-----------+-----------+-------+
+-- 0x10  |            START_L            |
+--       +-------------------------------+
+-- 0x11  |            START_H            |
+--       +-------+-----------+-----------+
+-- 0x12  |       |   OFF_Y   |   OFF_X   | OFFSET
+--       +-------+-----------+-----------+
+--
+-- COL_N:
+-- R/G/B color values for each of 16 palette colors
+--
+-- START_L/H: (TODO)
+-- Offset within screen buffer where tile (0, 0) should be read from
+-- Treated as a 16-bit-word address (only addresses even address within buffer)
+--
+-- OFF_X/Y: (TODO)
+-- Pixel offsets to apply when drawing tiles
+--
+--------------------------------------------------------------------------------
+-- WISHBONE DATASHEET
+--
+-- Wishbone specification used: Rev B.3
+-- Interface type: device
+-- Port size: 8-bit
+-- Operand sizes: 8-bit
+-- Endianness: undefined (port size same as granularity)
+-- Data transfer sequence: undefined
+-- Clock constraints: none
+-- Signals:
+-- * rst_i
+-- * clk_i
+-- * scr_cyc_i  (CYC_I for screen buffer)
+-- * tile_cyc_i (CYC_I for tile bitmaps)
+-- * pal_cyc_i  (CYC_I for RO palette registers)
+-- * stb_i
+-- * we_i
+-- * ack_o
+-- * adr_i (14-bit)
+-- * dat_i (8-bit)
+-- * dat_o (8-bit)
+--------------------------------------------------------------------------------
+
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.std_logic_misc.all;
+use ieee.numeric_std.all;
+
+library unisim;
+use unisim.vcomponents.all;
+
+library utility;
+
+library work;
+
+
+entity vga_tiler_opt is
+       port (
+               -- Wishbone SYSCON
+               rst_i:      in  std_logic;
+               clk_i:      in  std_logic;
+
+               -- System access to video ram
+               scr_cyc_i:  in  std_logic;
+               tile_cyc_i: in  std_logic;
+               pal_cyc_i:  in  std_logic;
+               stb_i:      in  std_logic;
+               we_i:       in  std_logic;
+               ack_o:      out std_logic;
+               adr_i:      in  std_logic_vector(13 downto 0);
+               dat_i:      in  std_logic_vector(7 downto 0);
+               dat_o:      out std_logic_vector(7 downto 0);
+
+               -- VGA config
+               vga_clk:    in  std_logic;  -- 50 MHz
+
+               -- VGA output
+               vgaRed:     out std_logic_vector(3 downto 1);
+               vgaGreen:   out std_logic_vector(3 downto 1);
+               vgaBlue:    out std_logic_vector(3 downto 2);
+               Hsync:      out std_logic;
+               Vsync:      out std_logic
+       );
+end vga_tiler_opt;
+
+
+architecture behavioral of vga_tiler_opt is
+
+       -- System Wishbone interface
+       type wb_state_t is (S_IDLE, S_ACK);
+       signal wb_state_reg:       wb_state_t;
+       signal wb_state_next:      wb_state_t;
+       signal char0_stb_i:        std_logic;
+       signal char1_stb_i:        std_logic;
+       signal char2_stb_i:        std_logic;
+       signal char3_stb_i:        std_logic;
+       signal char4_stb_i:        std_logic;
+       signal char5_stb_i:        std_logic;
+       signal char6_stb_i:        std_logic;
+       signal char7_stb_i:        std_logic;
+       signal tile_stb_i:         std_logic;
+       signal palette_we:         std_logic;
+       signal char0_dat_o:        std_logic_vector(7 downto 0);
+       signal char1_dat_o:        std_logic_vector(7 downto 0);
+       signal char2_dat_o:        std_logic_vector(7 downto 0);
+       signal char3_dat_o:        std_logic_vector(7 downto 0);
+       signal char4_dat_o:        std_logic_vector(7 downto 0);
+       signal char5_dat_o:        std_logic_vector(7 downto 0);
+       signal char6_dat_o:        std_logic_vector(7 downto 0);
+       signal char7_dat_o:        std_logic_vector(7 downto 0);
+       signal tile_dat_o:         std_logic_vector(7 downto 0);
+
+       -- BRAM is faster than the external ram, and is dual-ported to prevent bus
+       -- contention with whatever system is attached to the tiler.  BRAM is also
+       -- synchronous, which means it will take multiple clock cycles to process
+       -- each pixel - so a cheeky lil pipeline is needed.  Also, the BRAM cells
+       -- take separate clocks for each interface, which allows the VGA controller
+       -- to be driven at a different clock rate than the rest of the system, which
+       -- allows for new and exciting screen resolutions.
+
+       -- BRAM access is kept in its own separate stages for convenience.  Other
+       -- stages can be further split if higher performance is necessary.  The
+       -- output registers of the BRAM cells are treated as part of their
+       -- respective interstage registers.  Some signals (like all the bits of
+       -- pix_x and pix_y) are passed down the pipe even after they're strictly
+       -- necessary.  This is for convenience if more is added later, and they will
+       -- be trimmed by the specializer during synthesis.
+
+       -- Stage 0: Compute character location within screen buffer
+       signal s0_h_sync:          std_logic;
+       signal s0_v_sync:          std_logic;
+       signal s0_h_blank:         std_logic;
+       signal s0_v_blank:         std_logic;
+       signal s0_pix_x:           std_logic_vector(10 downto 0);
+       signal s0_pix_y:           std_logic_vector(9 downto 0);
+       signal s0_char_row:        unsigned(6 downto 0);
+       signal s0_char_col:        unsigned(6 downto 0);
+       signal s0_char_idx:        unsigned(12 downto 0);
+
+       -- Register 0-1
+       --signal s01_h_sync_reg:     std_logic;
+       --signal s01_v_sync_reg:     std_logic;
+       --signal s01_h_blank_reg:    std_logic;
+       --signal s01_v_blank_reg:    std_logic;
+       --signal s01_pix_x_reg:      std_logic_vector(10 downto 0);
+       --signal s01_pix_y_reg:      std_logic_vector(9 downto 0);
+       --signal s01_char_idx_reg:   unsigned(12 downto 0);
+
+       -- Stage 1: Lookup screen character's tile ID within screen buffer
+
+       -- Register 1-2
+       signal s12_h_sync_reg:     std_logic;
+       signal s12_v_sync_reg:     std_logic;
+       signal s12_h_blank_reg:    std_logic;
+       signal s12_v_blank_reg:    std_logic;
+       signal s12_pix_x_reg:      std_logic_vector(10 downto 0);
+       signal s12_pix_y_reg:      std_logic_vector(9 downto 0);
+       signal s12_char_idx_reg:   unsigned(12 downto 0);
+       signal s12_bank0_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank1_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank2_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank3_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank4_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank5_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank6_char_reg: std_logic_vector(15 downto 0);
+       signal s12_bank7_char_reg: std_logic_vector(15 downto 0);
+
+       -- Stage 2: Select the tile ID from the correct bank and compute tile location within tile ram
+       signal s2_charcol:         std_logic_vector(15 downto 0);
+       signal s2_char:            std_logic_vector(7 downto 0);
+       signal s2_color:           std_logic_vector(7 downto 0);
+       signal s2_tile_idx:        std_logic_vector(10 downto 0);
+
+       -- Register 2-3
+       --signal s23_h_sync_reg:     std_logic;
+       --signal s23_v_sync_reg:     std_logic;
+       --signal s23_h_blank_reg:    std_logic;
+       --signal s23_v_blank_reg:    std_logic;
+       --signal s23_pix_x_reg:      std_logic_vector(10 downto 0);
+       --signal s23_pix_y_reg:      std_logic_vector(9 downto 0);
+       --signal s23_tile_idx_reg:   std_logic_vector(10 downto 0);
+       --signal s23_color_reg:      std_logic_vector(7 downto 0);
+
+       -- Stage 3: Lookup tile slice within tile ram and colors in palette
+       signal s3_fg_palette_adr:  std_logic_vector(3 downto 0);
+       signal s3_bg_palette_adr:  std_logic_vector(3 downto 0);
+       signal s3_fg_color:        std_logic_vector(7 downto 0);
+       signal s3_bg_color:        std_logic_vector(7 downto 0);
+
+       -- Register 3-4
+       signal s34_h_sync_reg:     std_logic;
+       signal s34_v_sync_reg:     std_logic;
+       signal s34_h_blank_reg:    std_logic;
+       signal s34_v_blank_reg:    std_logic;
+       signal s34_pix_x_reg:      std_logic_vector(10 downto 0);
+       signal s34_pix_y_reg:      std_logic_vector(9 downto 0);
+       signal s34_fg_color_reg:   std_logic_vector(7 downto 0);
+       signal s34_bg_color_reg:   std_logic_vector(7 downto 0);
+       signal s34_tile_line_reg:  std_logic_vector(7 downto 0);
+
+       -- Stage 4: Select bit within tile slice an map to color
+       signal s4_bit:             std_logic;
+       signal s4_visible:         std_logic;
+       signal s4_vga_red:         std_logic_vector(3 downto 1);
+       signal s4_vga_green:       std_logic_vector(3 downto 1);
+       signal s4_vga_blue:        std_logic_vector(3 downto 2);
+
+       -- Register 4-output
+       signal s4o_h_sync_reg:     std_logic;
+       signal s4o_v_sync_reg:     std_logic;
+       signal s4o_vga_red_reg:    std_logic_vector(3 downto 1);
+       signal s4o_vga_green_reg:  std_logic_vector(3 downto 1);
+       signal s4o_vga_blue_reg:   std_logic_vector(3 downto 2);
+
+begin
+
+       ----------------------------------------------------------------------------
+       -- System Wishbone interface
+       -- FIXME: this may do double writes - not a problem for now though
+
+
+       process (rst_i, clk_i, wb_state_next)
+       begin
+               if rising_edge(clk_i) then
+                       if rst_i = '1' then
+                               wb_state_reg <= S_IDLE;
+                       else
+                               wb_state_reg <= wb_state_next;
+                       end if;
+               end if;
+       end process;
+
+       process (wb_state_reg, stb_i)
+       begin
+               wb_state_next <= wb_state_reg;
+               ack_o         <= '0';
+
+               case wb_state_reg is
+                       when S_IDLE =>
+                               if stb_i = '1' then
+                                       wb_state_next <= S_ACK;
+                               end if;
+
+                       when S_ACK =>
+                               ack_o         <= '1';
+                               wb_state_next <= S_IDLE;
+
+                       when others =>
+                               wb_state_next <= S_IDLE;
+               end case;
+       end process;
+
+       with tile_cyc_i & scr_cyc_i & adr_i(13 downto 11) select dat_o <=
+               char0_dat_o     when "01000",
+               char1_dat_o     when "01001",
+               char2_dat_o     when "01010",
+               char3_dat_o     when "01011",
+               char4_dat_o     when "01100",
+               char5_dat_o     when "01101",
+               char6_dat_o     when "01110",
+               char7_dat_o     when "01111",
+               tile_dat_o      when "10---",
+               (others => '1') when others;
+
+       char0_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "000" else '0';
+       char1_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "001" else '0';
+       char2_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "010" else '0';
+       char3_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "011" else '0';
+       char4_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "100" else '0';
+       char5_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "101" else '0';
+       char6_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "110" else '0';
+       char7_stb_i <= scr_cyc_i  and stb_i when adr_i(13 downto 11) = "111" else '0';
+       tile_stb_i  <= tile_cyc_i and stb_i;
+       palette_we  <= pal_cyc_i  and stb_i and we_i;
+
+
+       ----------------------------------------------------------------------------
+       -- (Stage -1: VGA pixel counter and signal generation)
+
+       e_vga_counter: entity work.vga_counter
+               port map (
+                       clk_50  => vga_clk,
+
+                       pix_x   => s0_pix_x,
+                       pix_y   => s0_pix_y,
+
+                       h_blank => s0_h_blank,
+                       v_blank => s0_v_blank,
+
+                       h_sync  => s0_h_sync,
+                       v_sync  => s0_v_sync
+               );
+
+
+       ----------------------------------------------------------------------------
+       -- Stage 0: Compute character location within screen buffer
+
+       -- Divide pixel positions by 8 to get row and column
+       s0_char_col <= unsigned(s0_pix_x(10 downto 4));
+       s0_char_row <= unsigned(s0_pix_y(9 downto 3));
+
+       -- Index into screen character buffer is row * 80 + col
+       -- Shouldn't carry for pix_x and pix_y within visible screen range, 13 bits is enough
+       -- Used for reads only, so nondestructive if out of visible screen range
+       s0_char_idx <= ((("00" & s0_char_row) + (s0_char_row & "00")) & "0000") + s0_char_col;
+
+
+       -- Register 0-1
+       --process (vga_clk, s0_h_sync, s0_v_sync, s0_h_blank, s0_v_blank, s0_pix_x, s0_pix_y, s0_char_idx)
+       --begin
+       --      if rising_edge(vga_clk) then
+       --              s01_h_sync_reg   <= s0_h_sync;
+       --              s01_v_sync_reg   <= s0_v_sync;
+       --              s01_h_blank_reg  <= s0_h_blank;
+       --              s01_v_blank_reg  <= s0_v_blank;
+       --              s01_pix_x_reg    <= s0_pix_x;
+       --              s01_pix_y_reg    <= s0_pix_y;
+       --              s01_char_idx_reg <= s0_char_idx;
+       --      end if;
+       --end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Stage 1: Look up screen character's tile ID within screen buffer
+
+
+       e_char_bank_0: ramb16_s9_s18
+               generic map (
+                       INIT_00 => x"1f1e1d1c1b1a191817161514131211100f0e0d0c0b0a09080706050403020100",
+                       INIT_01 => x"3f3e3d3c3b3a393837363534333231302f2e2d2c2b2a29282726252423222120",
+                       INIT_02 => x"5f5e5d5c5b5a595857565554535251504f4e4d4c4b4a49484746454443424140",
+                       INIT_03 => x"7f7e7d7c7b7a797877767574737271706f6e6d6c6b6a69686766656463626160",
+                       INIT_04 => x"9f9e9d9c9b9a999897969594939291908f8e8d8c8b8a89888786858483828180",
+                       INIT_05 => x"bfbebdbcbbbab9b8b7b6b5b4b3b2b1b0afaeadacabaaa9a8a7a6a5a4a3a2a1a0",
+                       INIT_06 => x"dfdedddcdbdad9d8d7d6d5d4d3d2d1d0cfcecdcccbcac9c8c7c6c5c4c3c2c1c0",
+                       INIT_07 => x"fffefdfcfbfaf9f8f7f6f5f4f3f2f1f0efeeedecebeae9e8e7e6e5e4e3e2e1e0"
+               )
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char0_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char0_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s0_char_idx(9 downto 0)),
+
+                       dob   => s12_bank0_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_1: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char1_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char1_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s0_char_idx(9 downto 0)),
+
+                       dob   => s12_bank1_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_2: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char2_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char2_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s0_char_idx(9 downto 0)),
+
+                       dob   => s12_bank2_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_3: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char3_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char3_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s0_char_idx(9 downto 0)),
+
+                       dob   => s12_bank3_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_4: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char4_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char4_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s0_char_idx(9 downto 0)),
+
+                       dob   => s12_bank4_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_5: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char5_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char5_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s0_char_idx(9 downto 0)),
+
+                       dob   => s12_bank5_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_6: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char6_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char6_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s0_char_idx(9 downto 0)),
+
+                       dob   => s12_bank6_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+       e_char_bank_7: ramb16_s9_s18
+               port map (
+                       -- Port A, 8-bit system access
+                       ssra  => rst_i,
+                       clka  => clk_i,
+                       ena   => char7_stb_i,
+                       wea   => we_i,
+                       addra => adr_i(10 downto 0),
+
+                       doa   => char7_dat_o,
+                       dopa  => open,
+                       dia   => dat_i,
+                       dipa  => "0",
+
+                       -- Port B, 16-bit tiler access
+                       ssrb  => rst_i,
+                       clkb  => vga_clk,
+                       enb   => '1',
+                       web   => '0',
+                       addrb => std_logic_vector(s0_char_idx(9 downto 0)),
+
+                       dob   => s12_bank7_char_reg,
+                       dopb  => open,
+                       dib   => (others => '0'),
+                       dipb  => "00"
+               );
+
+
+       -- Register 1-2
+       process (vga_clk, s0_h_sync, s0_v_sync, s0_h_blank, s0_v_blank, s0_pix_x, s0_pix_y, s0_char_idx)
+       begin
+               if rising_edge(vga_clk) then
+                       s12_h_sync_reg   <= s0_h_sync;
+                       s12_v_sync_reg   <= s0_v_sync;
+                       s12_h_blank_reg  <= s0_h_blank;
+                       s12_v_blank_reg  <= s0_v_blank;
+                       s12_pix_x_reg    <= s0_pix_x;
+                       s12_pix_y_reg    <= s0_pix_y;
+                       s12_char_idx_reg <= s0_char_idx;
+                       -- s12_bank0_char_reg
+                       -- s12_bank1_char_reg
+                       -- s12_bank2_char_reg
+                       -- s12_bank3_char_reg
+                       -- s12_bank4_char_reg
+                       -- s12_bank5_char_reg
+                       -- s12_bank6_char_reg
+                       -- s12_bank7_char_reg
+               end if;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Stage 2: Select the tile ID from the correct bank and compute tile location within tile ram
+
+
+       with s12_char_idx_reg(12 downto 10) select s2_charcol <=
+               s12_bank0_char_reg when "000",
+               s12_bank1_char_reg when "001",
+               s12_bank2_char_reg when "010",
+               s12_bank3_char_reg when "011",
+               s12_bank4_char_reg when "100",
+               s12_bank5_char_reg when "101",
+               s12_bank6_char_reg when "110",
+               s12_bank7_char_reg when "111",
+               (others => 'X')    when others;
+
+       s2_char     <= s2_charcol( 7 downto 0);
+       s2_color    <= s2_charcol(15 downto 8);
+       s2_tile_idx <= s2_char & s12_pix_y_reg(2 downto 0);
+
+
+       -- Register 2-3
+       --process (vga_clk, s12_h_sync_reg, s12_v_sync_reg, s12_h_blank_reg, s12_v_blank_reg, s12_pix_x_reg, s12_pix_y_reg, s2_tile_idx)
+       --begin
+       --      if rising_edge(vga_clk) then
+       --              s23_h_sync_reg   <= s12_h_sync_reg;
+       --              s23_v_sync_reg   <= s12_v_sync_reg;
+       --              s23_h_blank_reg  <= s12_h_blank_reg;
+       --              s23_v_blank_reg  <= s12_v_blank_reg;
+       --              s23_pix_x_reg    <= s12_pix_x_reg;
+       --              s23_pix_y_reg    <= s12_pix_y_reg;
+       --              s23_tile_idx_reg <= s2_tile_idx;
+       --              s23_color_reg    <= s2_color;
+       --      end if;
+       --end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Stage 3: Lookup tile slice within tile ram and colors from palette
+
+
+       e_tile_ram: ramb16_s9_s9
+               generic map (
+                       INIT_08 => x"006666ff66ff6666000000000066666600180000181818180000000000000000",
+                       INIT_09 => x"0000000000180c06003f6667383c663c00466630180c666200187c063c603e18",
+                       INIT_0A => x"000018187e1818000000663cff3c66000030180c0c0c1830000c18303030180c",
+                       INIT_0B => x"006030180c0603000018180000000000000000007e0000003018180000000000",
+                       INIT_0C => x"003c66061c06663c007e60300c06663c007e181818381818003c6666766e663c",
+                       INIT_0D => x"00181818180c667e003c66667c60663c003c6606067c607e0006067f661e0e06",
+                       INIT_0E => x"30181800001800000000180000180000003c66063e66663c003c66663c66663c",
+                       INIT_0F => x"001800180c06663c0070180c060c18700000007e007e0000000e18306030180e",
+                       INIT_10 => x"003c66606060663c007c66667c66667c006666667e663c18003c62606e6e663c",
+                       INIT_11 => x"003c66666e60663c006060607860607e007e60607860607e00786c6666666c78",
+                       INIT_12 => x"00666c7870786c6600386c0c0c0c0c1e003c18181818183c006666667e666666",
+                       INIT_13 => x"003c66666666663c0066666e7e7e7666006363636b7f7763007e606060606060",
+                       INIT_14 => x"003c66063c60663c00666c787c66667c000e3c666666663c006060607c66667c",
+                       INIT_15 => x"0063777f6b63636300183c6666666666003c666666666666001818181818187e",
+                       INIT_16 => x"003c30303030303c007e6030180c067e001818183c6666660066663c183c6666",
+                       INIT_17 => x"00000000000000000000000000000000003c0c0c0c0c0c3c0000000000000000",
+                       INIT_18 => x"003c6060603c0000007c66667c606000003e663e063c00000000000000000000",
+                       INIT_19 => x"7c063e66663e0000001818183e180e00003c607e663c0000003e66663e060600",
+                       INIT_1A => x"00666c786c6060003c06060606000600003c181838001800006666667c606000",
+                       INIT_1B => x"003c6666663c000000666666667c000000636b7f7f660000003c181818183800",
+                       INIT_1C => x"007c063c603e000000606060667c000006063e66663e000060607c66667c0000",
+                       INIT_1D => x"00363e7f6b63000000183c6666660000003e666666660000000e1818187e1800",
+                       INIT_1E => x"0000000000000000007e30180c7e0000780c3e666666000000663c183c660000"
+               )
+               port map (
+                       -- Port A, tiler access
+                       ssra  => rst_i,
+                       clka  => vga_clk,
+                       ena   => '1',
+                       wea   => '0',
+                       addra => s2_tile_idx,
+
+                       doa   => s34_tile_line_reg,
+                       dopa  => open,
+                       dia   => (others => '0'),
+                       dipa  => "0",
+
+                       -- Port B, system access
+                       ssrb  => rst_i,
+                       clkb  => clk_i,
+                       enb   => tile_stb_i,
+                       web   => we_i,
+                       addrb => adr_i(10 downto 0),
+
+                       dob   => tile_dat_o,
+                       dopb  => open,
+                       dib   => dat_i,
+                       dipb  => "0"
+               );
+
+       -- Palette reads are asynchronous and writes should only happen during
+       -- blanking intervals, so it's probably fine to have writes happen in a
+       -- different clock domain
+       e_palette: entity utility.reg_file_1w2r
+               generic map (A => 4, N => 8)
+               port map (
+                       clk_a_i => clk_i,
+                       we_a_i  => palette_we,
+                       adr_a_i => adr_i(3 downto 0),
+                       dat_a_i => dat_i,
+
+                       adr_b_i => s3_fg_palette_adr,
+                       dat_b_o => s3_fg_color,
+
+                       adr_c_i => s3_bg_palette_adr,
+                       dat_c_o => s3_bg_color
+               );
+
+       s3_fg_palette_adr <= s2_color(3 downto 0);
+       s3_bg_palette_adr <= s2_color(7 downto 4);
+
+
+       -- Register 3-4
+       process (vga_clk, s12_h_sync_reg, s12_v_sync_reg, s12_h_blank_reg, s12_v_blank_reg, s12_pix_x_reg, s12_pix_y_reg)
+       begin
+               if rising_edge(vga_clk) then
+                       s34_h_sync_reg   <= s12_h_sync_reg;
+                       s34_v_sync_reg   <= s12_v_sync_reg;
+                       s34_h_blank_reg  <= s12_h_blank_reg;
+                       s34_v_blank_reg  <= s12_v_blank_reg;
+                       s34_pix_x_reg    <= s12_pix_x_reg;
+                       s34_pix_y_reg    <= s12_pix_y_reg;
+                       s34_fg_color_reg <= s3_fg_color;
+                       s34_bg_color_reg <= s3_bg_color;
+                       -- s34_tile_line_reg
+               end if;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Stage 4: Select bit within tile slice an map to color
+
+
+       s4_bit       <= s34_tile_line_reg(to_integer(unsigned(not s34_pix_x_reg(3 downto 1))));
+       s4_visible   <= not (s34_h_blank_reg or s34_v_blank_reg);
+
+       -- s4_vga_red   <= "111" when (s4_visible and s4_bit) = '1' else "000";
+       -- s4_vga_green <= "111" when (s4_visible and s4_bit) = '1' else "000";
+       -- s4_vga_blue  <= "11"  when (s4_visible and s4_bit) = '1' else "00";
+       s4_vga_red   <= s34_fg_color_reg(7 downto 5) when (s4_visible and s4_bit) = '1' else s34_bg_color_reg(7 downto 5);
+       s4_vga_green <= s34_fg_color_reg(4 downto 2) when (s4_visible and s4_bit) = '1' else s34_bg_color_reg(4 downto 2);
+       s4_vga_blue  <= s34_fg_color_reg(1 downto 0) when (s4_visible and s4_bit) = '1' else s34_bg_color_reg(1 downto 0);
+
+
+       -- Register 4-output
+       process (vga_clk, s34_h_sync_reg, s34_v_sync_reg, s4_vga_red, s4_vga_green, s4_vga_blue)
+       begin
+               if rising_edge(vga_clk) then
+                       s4o_h_sync_reg    <= s34_h_sync_reg;
+                       s4o_v_sync_reg    <= s34_v_sync_reg;
+                       s4o_vga_red_reg   <= s4_vga_red;
+                       s4o_vga_green_reg <= s4_vga_green;
+                       s4o_vga_blue_reg  <= s4_vga_blue;
+               end if;
+       end process;
+
+
+       ----------------------------------------------------------------------------
+       -- Output
+
+
+       Hsync    <= s4o_h_sync_reg;
+       Vsync    <= s4o_v_sync_reg;
+       vgaRed   <= s4o_vga_red_reg;
+       vgaGreen <= s4o_vga_green_reg;
+       vgaBlue  <= s4o_vga_blue_reg;
+
+end behavioral;
index 08c97cdfbd56e21fd27254685c19e31a5d8dfc7a..1ee6cd58f4233641455955ace77ec1deb6674dfb 100644 (file)
@@ -1,37 +1,42 @@
+( VGA region bases )
+vga_scr=0x02000000
+vga_tile=0x02004000
+vga_pal=0x02006000
+
 ( host registers )
-host_ctrl=0x02004000
-host_flags=0x02004001
-host_mbox=0x02004002
-host_swled=0x02004003
-host_sseg0=0x02004004
-host_sseg1=0x02004005
-host_sseg2=0x02004006
-host_sseg3=0x02004007
+host_ctrl=0x02008000
+host_flags=0x02008001
+host_mbox=0x02008002
+host_swled=0x02008003
+host_sseg0=0x02008004
+host_sseg1=0x02008005
+host_sseg2=0x02008006
+host_sseg3=0x02008007
 
 ( ps2 registers )
-ps2_ctrl=0x02004008
-ps2_imask=0x02004009
-ps2_iflag=0x0200400a
-ps2_error=0x0200400b
-ps2_data=0x0200400c
+ps2_ctrl=0x02008008
+ps2_imask=0x02008009
+ps2_iflag=0x0200800a
+ps2_error=0x0200800b
+ps2_data=0x0200800c
 
 ( rs232 registers )
-uart_ctrl=0x02004010
-uart_baudl=0x02004011
-uart_baudh=0x02004012
-uart_imask=0x02004013
-uart_iflag=0x02004014
-uart_data=0x02004015
+uart_ctrl=0x02008010
+uart_baudl=0x02008011
+uart_baudh=0x02008012
+uart_imask=0x02008013
+uart_iflag=0x02008014
+uart_data=0x02008015
 
 ( timer registers )
-timer0_ctrl=0x02004018
-timer0_count_l=0x02004019
-timer0_count_m=0x0200401a
-timer0_count_h=0x0200401b
-timer1_ctrl=0x0200401c
-timer1_count_l=0x0200401d
-timer1_count_m=0x0200401e
-timer1_count_h=0x0200401f
+timer0_ctrl=0x02008018
+timer0_count_l=0x02008019
+timer0_count_m=0x0200801a
+timer0_count_h=0x0200801b
+timer1_ctrl=0x0200801c
+timer1_count_l=0x0200801d
+timer1_count_m=0x0200801e
+timer1_count_h=0x0200801f
 
 
 ( ivec -- )
@@ -120,5 +125,43 @@ isr_unk:
 
 
 start:
+    ( Write palette )
+    #8 0x00i8 #32 vga_pal #8 0x00i8 + !8 drop
+    #8 0x60i8 #32 vga_pal #8 0x01i8 + !8 drop
+    #8 0x0ci8 #32 vga_pal #8 0x02i8 + !8 drop
+    #8 0x01i8 #32 vga_pal #8 0x03i8 + !8 drop
+    #8 0x6ci8 #32 vga_pal #8 0x04i8 + !8 drop
+    #8 0x0di8 #32 vga_pal #8 0x05i8 + !8 drop
+    #8 0x61i8 #32 vga_pal #8 0x06i8 + !8 drop
+    #8 0x6di8 #32 vga_pal #8 0x07i8 + !8 drop
+    #8 0x92i8 #32 vga_pal #8 0x08i8 + !8 drop
+    #8 0xe0i8 #32 vga_pal #8 0x09i8 + !8 drop
+    #8 0x1ci8 #32 vga_pal #8 0x0ai8 + !8 drop
+    #8 0x03i8 #32 vga_pal #8 0x0bi8 + !8 drop
+    #8 0xfci8 #32 vga_pal #8 0x0ci8 + !8 drop
+    #8 0x1fi8 #32 vga_pal #8 0x0di8 + !8 drop
+    #8 0xe3i8 #32 vga_pal #8 0x0ei8 + !8 drop
+    #8 0xffi8 #32 vga_pal #8 0x0fi8 + !8 drop
+
+    ( Send greetz to the l33tz )
+    #8 "H"    #32 vga_scr #8 0i8  + !8 drop
+    #8 0x21i8 #32 vga_scr #8 1i8  + !8 drop
+    #8 "e"    #32 vga_scr #8 2i8  + !8 drop
+    #8 0x32i8 #32 vga_scr #8 3i8  + !8 drop
+    #8 "l"    #32 vga_scr #8 4i8  + !8 drop
+    #8 0x43i8 #32 vga_scr #8 5i8  + !8 drop
+    #8 "l"    #32 vga_scr #8 6i8  + !8 drop
+    #8 0x54i8 #32 vga_scr #8 7i8  + !8 drop
+    #8 "o"    #32 vga_scr #8 8i8  + !8 drop
+    #8 0x65i8 #32 vga_scr #8 9i8  + !8 drop
+    #8 "r"    #32 vga_scr #8 10i8 + !8 drop
+    #8 0x76i8 #32 vga_scr #8 11i8 + !8 drop
+    #8 "l"    #32 vga_scr #8 12i8 + !8 drop
+    #8 0x87i8 #32 vga_scr #8 13i8 + !8 drop
+    #8 "d"    #32 vga_scr #8 14i8 + !8 drop
+    #8 0x98i8 #32 vga_scr #8 15i8 + !8 drop
+    #8 "!"    #32 vga_scr #8 16i8 + !8 drop
+    #8 0xa9i8 #32 vga_scr #8 17i8 + !8 drop
+
 halt:
     jmp halt
index 4e44ee857e8c6bfe468a5efc984c1a0361f46365..a91272196e4f0f41485ba3525e29e13c7b9acca5 100644 (file)
@@ -7,6 +7,7 @@ library nexys2_lib;
 library ps2;
 library rs232;
 library vga;
+library timer;
 
 
 entity nexys2 is
@@ -83,9 +84,11 @@ architecture behavioral of nexys2 is
        signal mem_ack:           std_logic;
        signal mem_miso:          std_logic_vector(7 downto 0);
 
+       signal scr_cyc:           std_logic;
        signal tile_cyc:          std_logic;
-       signal tile_ack:          std_logic;
-       signal tile_miso:         std_logic_vector(7 downto 0);
+       signal pal_cyc:           std_logic;
+       signal vga_ack:           std_logic;
+       signal vga_miso:          std_logic_vector(7 downto 0);
 
        signal host_cyc:          std_logic;
        signal host_ack:          std_logic;
@@ -156,14 +159,14 @@ architecture behavioral of nexys2 is
        signal ints:              std_logic_vector(15 downto 0);
 
        -- Debug signals
-       signal deb_wait: std_logic;
-       signal deb_pc:   std_logic_vector(31 downto 0);
-       signal deb_ins:  std_logic_vector(7 downto 0);
-       signal deb_t:    std_logic_vector(31 downto 0);
-       signal deb_n:    std_logic_vector(31 downto 0);
-       signal deb_r:    std_logic_vector(31 downto 0);
-       signal debug_i:  std_logic_vector(63 downto 0);
-       signal debug_o:  std_logic_vector(63 downto 0);
+       signal deb_wait:          std_logic;
+       signal deb_pc:            std_logic_vector(31 downto 0);
+       signal deb_ins:           std_logic_vector(7 downto 0);
+       signal deb_t:             std_logic_vector(31 downto 0);
+       signal deb_n:             std_logic_vector(31 downto 0);
+       signal deb_r:             std_logic_vector(31 downto 0);
+       signal debug_i:           std_logic_vector(63 downto 0);
+       signal debug_o:           std_logic_vector(63 downto 0);
 
 begin
 
@@ -210,16 +213,19 @@ begin
        d_clk <= clk_50;
 
 
-       -- Flash: 0x00000000-0x00ffffff
-       -- Ram:   0x01000000-0x01ffffff
-       -- Vbuf:  0x02000000-0x02001fff
-       -- Tiles: 0x02002000-0x02003fff
-       -- Host:  0x02004000-0x02004007
-       -- PS2:   0x02004008-0x0200400f
-       -- UART:  0x02004010-0x02004017
+       -- Flash:   0x00000000-0x00ffffff
+       -- Ram:     0x01000000-0x01ffffff
+       -- Vbuf:    0x02000000-0x02003fff
+       -- Tiles:   0x02004000-0x020047ff
+       -- Palette: 0x02006000-0x02007fff
+       -- Host:    0x02008000-0x02008007
+       -- PS2:     0x02008008-0x0200800f
+       -- UART:    0x02008010-0x02008017
+       -- Timer0:  0x02008018-0x0200801b
+       -- Timer1:  0x0200801c-0x0200801f
        e_mapper: entity utility.wb_mapper_a32d8
                generic map (
-                       N => 8
+                       N => 10
                )
                port map (
                        cyc_i    => cyc,
@@ -227,50 +233,60 @@ begin
                        adr_i    => adr,
                        dat_o    => dat_miso,
 
-                       mask(0)  => "00000011000000000000000000000000",
-                       mask(1)  => "00000011000000000000000000000000",
-                       mask(2)  => "00000010000000000100000000000000",
-                       mask(3)  => "00000010000000000100000000011000",
-                       mask(4)  => "00000010000000000100000000011000",
-                       mask(5)  => "00000010000000000100000000011000",
-                       mask(6)  => "00000010000000000100000000011100",
-                       mask(7)  => "00000010000000000100000000011100",
+                       mask(0)  => "00000011000000000000000000000000",  -- Flash
+                       mask(1)  => "00000011000000000000000000000000",  -- RAM
+                       mask(2)  => "00000010000000001100000000000000",  -- VGA screen buffer
+                       mask(3)  => "00000010000000001110000000000000",  -- VGA tile memory
+                       mask(4)  => "00000010000000001110000000000000",  -- VGA palette
+                       mask(5)  => "00000010000000001100000000011000",  -- Host
+                       mask(6)  => "00000010000000001100000000011000",  -- PS2
+                       mask(7)  => "00000010000000001100000000011000",  -- UART
+                       mask(8)  => "00000010000000001100000000011100",  -- Timer0
+                       mask(9)  => "00000010000000001100000000011100",  -- Timer1
 
                        match(0) => "00000000000000000000000000000000",
                        match(1) => "00000001000000000000000000000000",
-                       match(2) => "00000010000000000000000000000000",
-                       match(3) => "00000010000000000100000000000000",
-                       match(4) => "00000010000000000100000000001000",
-                       match(5) => "00000010000000000100000000010000",
-                       match(6) => "00000010000000000100000000011000",
-                       match(7) => "00000010000000000100000000011100",
+                       match(2) => "00000010000000000000000000000000",  -- VGA scrbuf
+                       match(3) => "00000010000000000100000000000000",  -- VGA tiles
+                       match(4) => "00000010000000000110000000000000",  -- VGA palette
+                       match(5) => "00000010000000001000000000000000",
+                       match(6) => "00000010000000001000000000001000",
+                       match(7) => "00000010000000001000000000010000",
+                       match(8) => "00000010000000001000000000011000",
+                       match(9) => "00000010000000001000000000011100",
 
                        cyc_o(0) => fls_cyc,
                        cyc_o(1) => ram_cyc,
-                       cyc_o(2) => tile_cyc,
-                       cyc_o(3) => host_cyc,
-                       cyc_o(4) => ps2_cyc,
-                       cyc_o(5) => uart_cyc,
-                       cyc_o(6) => timer0_cyc,
-                       cyc_o(7) => timer1_cyc,
+                       cyc_o(2) => scr_cyc,
+                       cyc_o(3) => tile_cyc,
+                       cyc_o(4) => pal_cyc,
+                       cyc_o(5) => host_cyc,
+                       cyc_o(6) => ps2_cyc,
+                       cyc_o(7) => uart_cyc,
+                       cyc_o(8) => timer0_cyc,
+                       cyc_o(9) => timer1_cyc,
 
                        ack_i(0) => mem_ack,
                        ack_i(1) => mem_ack,
-                       ack_i(2) => tile_ack,
-                       ack_i(3) => host_ack,
-                       ack_i(4) => ps2_ack,
-                       ack_i(5) => uart_ack,
-                       ack_i(6) => timer0_ack,
-                       ack_i(7) => timer1_ack,
+                       ack_i(2) => vga_ack,
+                       ack_i(3) => vga_ack,
+                       ack_i(4) => vga_ack,
+                       ack_i(5) => host_ack,
+                       ack_i(6) => ps2_ack,
+                       ack_i(7) => uart_ack,
+                       ack_i(8) => timer0_ack,
+                       ack_i(9) => timer1_ack,
 
                        dat_i(0) => mem_miso,
                        dat_i(1) => mem_miso,
-                       dat_i(2) => tile_miso,
-                       dat_i(3) => host_miso,
-                       dat_i(4) => ps2_miso,
-                       dat_i(5) => uart_miso,
-                       dat_i(6) => timer0_miso,
-                       dat_i(7) => timer1_miso
+                       dat_i(2) => vga_miso,
+                       dat_i(3) => vga_miso,
+                       dat_i(4) => vga_miso,
+                       dat_i(5) => host_miso,
+                       dat_i(6) => ps2_miso,
+                       dat_i(7) => uart_miso,
+                       dat_i(8) => timer0_miso,
+                       dat_i(9) => timer1_miso
                );
 
 
@@ -313,24 +329,28 @@ begin
 
        e_vga: entity vga.vga_tiler
                port map (
-                       rst_i    => d_rst,
-                       clk_i    => d_clk,
+                       rst_i      => d_rst,
+                       clk_i      => d_clk,
 
                        -- Internal access to screen buffer and tile set
-                       cyc_i    => tile_cyc,
-                       stb_i    => stb,
-                       we_i     => we,
-                       ack_o    => tile_ack,
-                       adr_i    => adr(13 downto 0),
-                       dat_i    => dat_mosi,
-                       dat_o    => tile_miso,
+                       scr_cyc_i  => scr_cyc,
+                       tile_cyc_i => tile_cyc,
+                       pal_cyc_i  => pal_cyc,
+                       stb_i      => stb,
+                       we_i       => we,
+                       ack_o      => vga_ack,
+                       adr_i      => adr(13 downto 0),
+                       dat_i      => dat_mosi,
+                       dat_o      => vga_miso,
+
+                       vga_clk    => d_clk,  -- TODO: Plug this into a DCM
 
                        -- External pins
-                       vgaRed   => vgaRed,
-                       vgaGreen => vgaGreen,
-                       vgaBlue  => vgaBlue,
-                       Hsync    => Hsync,
-                       Vsync    => Vsync
+                       vgaRed     => vgaRed,
+                       vgaGreen   => vgaGreen,
+                       vgaBlue    => vgaBlue,
+                       Hsync      => Hsync,
+                       Vsync      => Vsync
                );
 
 
diff --git a/projects/cpu_0/nexys2_opt.vhd b/projects/cpu_0/nexys2_opt.vhd
new file mode 100644 (file)
index 0000000..b363f22
--- /dev/null
@@ -0,0 +1,535 @@
+library ieee;
+use ieee.std_logic_1164.all;
+use ieee.std_logic_misc.all;
+
+library utility;
+library nexys2_lib;
+library ps2;
+library rs232;
+library vga;
+library timer;
+
+
+entity nexys2_opt is
+       port (
+               -- Clock input
+               clk_50:     in    std_logic;
+
+               -- EPP interface
+               DB:         inout std_logic_vector(7 downto 0);
+               EppWRITE:   in    std_logic;
+               EppASTB:    in    std_logic;
+               EppDSTB:    in    std_logic;
+               EppWAIT:    out   std_logic;
+
+               -- Memory interface
+               MemOE:      out   std_logic;
+               MemWR:      out   std_logic;
+               RamAdv:     out   std_logic;
+               RamCS:      out   std_logic;
+               RamClk:     out   std_logic;
+               RamCRE:     out   std_logic;
+               RamLB:      out   std_logic;
+               RamUB:      out   std_logic;
+               RamWait:    in    std_logic;
+               FlashRp:    out   std_logic;
+               FlashCS:    out   std_logic;
+               FlashStSts: in    std_logic;
+               MemAdr:     out   std_logic_vector(23 downto 1);
+               MemDB:      inout std_logic_vector(15 downto 0);
+
+               -- Switches and LEDs
+               seg:        out   std_logic_vector(6 downto 0);
+               dp:         out   std_logic;
+               an:         out   std_logic_vector(3 downto 0);
+               Led:        out   std_logic_vector(7 downto 0);
+               sw:         in    std_logic_vector(7 downto 0);
+               btn:        in    std_logic_vector(3 downto 0);
+
+               -- VGA video output
+               vgaRed:     out   std_logic_vector(3 downto 1);
+               vgaGreen:   out   std_logic_vector(3 downto 1);
+               vgaBlue:    out   std_logic_vector(3 downto 2);
+               Hsync:      out   std_logic;
+               Vsync:      out   std_logic;
+
+               -- PS2 (keyboard)
+               PS2C:       inout std_logic;
+               PS2D:       inout std_logic;
+
+               -- RS232 (mouse)
+               RsRx:       in    std_logic;
+               RsTx:       out   std_logic
+       );
+end nexys2_opt;
+
+
+architecture behavioral of nexys2_opt is
+
+       -- Device Wishbone SYSCON
+       signal d_rst:             std_logic;  -- Device reset (P.O.R. or host)
+       signal d_clk:             std_logic;  -- Device clock, in case DCM used instead of clk_50 later
+
+       -- Wishbone busses
+       signal cyc:               std_logic;
+       signal stb:               std_logic;
+       signal we:                std_logic;
+       signal ack:               std_logic;
+       signal adr:               std_logic_vector(31 downto 0);
+       signal dat_mosi:          std_logic_vector(7 downto 0);
+       signal dat_miso:          std_logic_vector(7 downto 0);
+
+       signal fls_cyc:           std_logic;
+       signal ram_cyc:           std_logic;
+       signal mem_ack:           std_logic;
+       signal mem_miso:          std_logic_vector(7 downto 0);
+
+       signal scr_cyc:           std_logic;
+       signal tile_cyc:          std_logic;
+       signal pal_cyc:           std_logic;
+       signal vga_ack:           std_logic;
+       signal vga_miso:          std_logic_vector(7 downto 0);
+
+       signal host_cyc:          std_logic;
+       signal host_ack:          std_logic;
+       signal host_miso:         std_logic_vector(7 downto 0);
+
+       signal ps2_cyc:           std_logic;
+       signal ps2_ack:           std_logic;
+       signal ps2_miso:          std_logic_vector(7 downto 0);
+
+       signal uart_cyc:          std_logic;
+       signal uart_ack:          std_logic;
+       signal uart_miso:         std_logic_vector(7 downto 0);
+
+       signal timer0_cyc:        std_logic;
+       signal timer0_ack:        std_logic;
+       signal timer0_miso:       std_logic_vector(7 downto 0);
+
+       signal timer1_cyc:        std_logic;
+       signal timer1_ack:        std_logic;
+       signal timer1_miso:       std_logic_vector(7 downto 0);
+
+       -- Interrupt signals
+       signal host_flags:        std_logic_vector(7 downto 0);
+
+       signal ps2_rx_ready:      std_logic;
+       signal ps2_rx_full:       std_logic;
+       signal ps2_tx_ready:      std_logic;
+       signal ps2_tx_empty:      std_logic;
+       signal ps2_err_nack:      std_logic;
+       signal ps2_err_txto:      std_logic;
+       signal ps2_err_rxto:      std_logic;
+       signal ps2_err_missed:    std_logic;
+       signal ps2_err_parity:    std_logic;
+       signal ps2_err_framing:   std_logic;
+
+       signal uart_rx_ready:     std_logic;
+       signal uart_rx_full:      std_logic;
+       signal uart_tx_ready:     std_logic;
+       signal uart_tx_empty:     std_logic;
+       signal uart_err_break:    std_logic;
+       signal uart_err_framing:  std_logic;
+       signal uart_err_parity:   std_logic;
+       signal uart_err_overflow: std_logic;
+
+       signal timer0_zero:       std_logic;
+       signal timer1_zero:       std_logic;
+
+       -- Memory physical interface, routed through host controller
+       signal d_MemOE:           std_logic;
+       signal d_MemWR:           std_logic;
+       signal d_RamAdv:          std_logic;
+       signal d_RamCS:           std_logic;
+       signal d_RamClk:          std_logic;
+       signal d_RamCRE:          std_logic;
+       signal d_RamUB:           std_logic;
+       signal d_RamLB:           std_logic;
+       signal d_RamWait:         std_logic;
+       signal d_FlashRp:         std_logic;
+       signal d_FlashCS:         std_logic;
+       signal d_FlashStSts:      std_logic;
+       signal d_MemAdr:          std_logic_vector(23 downto 1);
+       signal d_MemDB_i:         std_logic_vector(15 downto 0);
+       signal d_MemDB_o:         std_logic_vector(15 downto 0);
+
+       -- Interrupt signals
+       signal int_cpu:           std_logic;
+       signal int_vec:           std_logic_vector(7 downto 0);
+       signal ints:              std_logic_vector(15 downto 0);
+
+       -- Debug signals
+       signal deb_wait:          std_logic;
+       signal deb_pc:            std_logic_vector(31 downto 0);
+       signal deb_ins:           std_logic_vector(7 downto 0);
+       signal deb_t:             std_logic_vector(31 downto 0);
+       signal deb_n:             std_logic_vector(31 downto 0);
+       signal deb_r:             std_logic_vector(31 downto 0);
+       signal debug_i:           std_logic_vector(63 downto 0);
+       signal debug_o:           std_logic_vector(63 downto 0);
+
+begin
+
+       e_cpu: entity work.cpu
+               port map (
+                       rst_i => d_rst,
+                       clk_i => d_clk,
+
+                       cyc_o => cyc,
+                       stb_o => stb,
+                       we_o  => we,
+                       ack_i => ack,
+                       adr_o => adr,
+                       dat_o => dat_mosi,
+                       dat_i => dat_miso,
+
+                       int_i => int_cpu,
+                       vec_i => int_vec,
+
+                       halt_i => sw(7),
+                       step_i => deb_wait,
+                       pc_o  => deb_pc,
+                       ins_o => deb_ins,
+                       t_o   => deb_t,
+                       n_o   => deb_n,
+                       r_o   => deb_r
+               );
+
+       deb_wait <= debug_i(0);
+       with debug_i(2 downto 1) select debug_o <=
+               x"000000" & deb_ins & deb_pc when "00",
+               deb_n & deb_t                when "01",
+               x"00000000" & deb_r          when others;
+
+       int_vec(7 downto 4) <= (others => '0');
+       ints(0) <= '0';
+       e_int: entity work.int_ctrl
+               port map (
+                       int_o => int_cpu,
+                       vec_o => int_vec(3 downto 0),
+                       int_i => ints
+               );
+
+       d_clk <= clk_50;
+
+
+       -- Flash:   0x00000000-0x00ffffff
+       -- Ram:     0x01000000-0x01ffffff
+       -- Vbuf:    0x02000000-0x02003fff
+       -- Tiles:   0x02004000-0x020047ff
+       -- Palette: 0x02006000-0x02007fff
+       -- Host:    0x02008000-0x02008007
+       -- PS2:     0x02008008-0x0200800f
+       -- UART:    0x02008010-0x02008017
+       -- Timer0:  0x02008018-0x0200801b
+       -- Timer1:  0x0200801c-0x0200801f
+       e_mapper: entity utility.wb_mapper_a32d8
+               generic map (
+                       N => 10
+               )
+               port map (
+                       cyc_i    => cyc,
+                       ack_o    => ack,
+                       adr_i    => adr,
+                       dat_o    => dat_miso,
+
+                       mask(0)  => "00000011000000000000000000000000",  -- Flash
+                       mask(1)  => "00000011000000000000000000000000",  -- RAM
+                       mask(2)  => "00000010000000001100000000000000",  -- VGA screen buffer
+                       mask(3)  => "00000010000000001110000000000000",  -- VGA tile memory
+                       mask(4)  => "00000010000000001110000000000000",  -- VGA palette
+                       mask(5)  => "00000010000000001100000000011000",  -- Host
+                       mask(6)  => "00000010000000001100000000011000",  -- PS2
+                       mask(7)  => "00000010000000001100000000011000",  -- UART
+                       mask(8)  => "00000010000000001100000000011100",  -- Timer0
+                       mask(9)  => "00000010000000001100000000011100",  -- Timer1
+
+                       match(0) => "00000000000000000000000000000000",
+                       match(1) => "00000001000000000000000000000000",
+                       match(2) => "00000010000000000000000000000000",  -- VGA scrbuf
+                       match(3) => "00000010000000000100000000000000",  -- VGA tiles
+                       match(4) => "00000010000000000110000000000000",  -- VGA palette
+                       match(5) => "00000010000000001000000000000000",
+                       match(6) => "00000010000000001000000000001000",
+                       match(7) => "00000010000000001000000000010000",
+                       match(8) => "00000010000000001000000000011000",
+                       match(9) => "00000010000000001000000000011100",
+
+                       cyc_o(0) => fls_cyc,
+                       cyc_o(1) => ram_cyc,
+                       cyc_o(2) => scr_cyc,
+                       cyc_o(3) => tile_cyc,
+                       cyc_o(4) => pal_cyc,
+                       cyc_o(5) => host_cyc,
+                       cyc_o(6) => ps2_cyc,
+                       cyc_o(7) => uart_cyc,
+                       cyc_o(8) => timer0_cyc,
+                       cyc_o(9) => timer1_cyc,
+
+                       ack_i(0) => mem_ack,
+                       ack_i(1) => mem_ack,
+                       ack_i(2) => vga_ack,
+                       ack_i(3) => vga_ack,
+                       ack_i(4) => vga_ack,
+                       ack_i(5) => host_ack,
+                       ack_i(6) => ps2_ack,
+                       ack_i(7) => uart_ack,
+                       ack_i(8) => timer0_ack,
+                       ack_i(9) => timer1_ack,
+
+                       dat_i(0) => mem_miso,
+                       dat_i(1) => mem_miso,
+                       dat_i(2) => vga_miso,
+                       dat_i(3) => vga_miso,
+                       dat_i(4) => vga_miso,
+                       dat_i(5) => host_miso,
+                       dat_i(6) => ps2_miso,
+                       dat_i(7) => uart_miso,
+                       dat_i(8) => timer0_miso,
+                       dat_i(9) => timer1_miso
+               );
+
+
+       e_mem: entity nexys2_lib.mem_wb8_0_opt
+               port map (
+                       rst_i       => d_rst,
+                       clk_i       => d_clk,
+
+                       -- Internal access
+                       fls_cyc_i   => fls_cyc,
+                       ram_cyc_i   => ram_cyc,
+                       stb_i       => stb,
+                       we_i        => we,
+                       ack_o       => mem_ack,
+                       adr_i       => adr(23 downto 0),
+                       dat_i       => dat_mosi,
+                       dat_o       => mem_miso,
+
+                       -- Configuration
+                       --wait_cycles => "01100",
+
+                       -- Memory interface
+                       MemOE       => d_MemOE,
+                       MemWR       => d_MemWR,
+                       RamAdv      => d_RamAdv,
+                       RamCS       => d_RamCS,
+                       RamClk      => d_RamClk,
+                       RamCRE      => d_RamCRE,
+                       RamUB       => d_RamUB,
+                       RamLB       => d_RamLB,
+                       RamWait     => d_RamWait,
+                       FlashRp     => d_FlashRp,
+                       FlashCS     => d_FlashCS,
+                       FlashStSts  => d_FlashStSts,
+                       MemAdr      => d_MemAdr,
+                       MemDB_i     => d_MemDB_i,
+                       MemDB_o     => d_MemDB_o
+               );
+
+
+       e_vga: entity vga.vga_tiler_opt
+               port map (
+                       rst_i      => d_rst,
+                       clk_i      => d_clk,
+
+                       -- Internal access to screen buffer and tile set
+                       scr_cyc_i  => scr_cyc,
+                       tile_cyc_i => tile_cyc,
+                       pal_cyc_i  => pal_cyc,
+                       stb_i      => stb,
+                       we_i       => we,
+                       ack_o      => vga_ack,
+                       adr_i      => adr(13 downto 0),
+                       dat_i      => dat_mosi,
+                       dat_o      => vga_miso,
+
+                       vga_clk    => d_clk,  -- TODO: Plug this into a DCM
+
+                       -- External pins
+                       vgaRed     => vgaRed,
+                       vgaGreen   => vgaGreen,
+                       vgaBlue    => vgaBlue,
+                       Hsync      => Hsync,
+                       Vsync      => Vsync
+               );
+
+
+       ints(1) <= or_reduce(host_flags);
+       e_host: entity nexys2_lib.host_ctrl
+               port map (
+                       clk_i        => d_clk,
+                       rst_i        => '0',
+
+                       -- Signals to the internal device
+                       d_rst_o      => d_rst,
+                       d_flags_o    => host_flags,
+                       debug_i      => debug_o,
+                       debug_o      => debug_i,
+
+                       -- Internal access to control registers
+                       d_cyc_i      => host_cyc,
+                       d_stb_i      => stb,
+                       d_we_i       => we,
+                       d_ack_o      => host_ack,
+                       d_adr_i      => adr(2 downto 0),
+                       d_dat_i      => dat_mosi,
+                       d_dat_o      => host_miso,
+
+                       -- Internal memory interface, can be switched off to allow the host to control memory
+                       d_MemOE      => d_MemOE,
+                       d_MemWR      => d_MemWR,
+                       d_RamAdv     => d_RamAdv,
+                       d_RamCS      => d_RamCS,
+                       d_RamClk     => d_RamClk,
+                       d_RamCRE     => d_RamCRE,
+                       d_RamLB      => d_RamLB,
+                       d_RamUB      => d_RamUB,
+                       d_RamWait    => d_RamWait,
+                       d_FlashRp    => d_FlashRp,
+                       d_FlashCS    => d_FlashCS,
+                       d_FlashStSts => d_FlashStSts,
+                       d_MemAdr     => d_MemAdr,
+                       d_MemDB_o    => d_MemDB_o,
+                       d_MemDB_i    => d_MemDB_i,
+
+                       -- External pins
+                       EppAstb      => EppASTB,
+                       EppDstb      => EppDSTB,
+                       EppWr        => EppWRITE,
+                       EppDB        => DB,
+                       EppWait      => EppWAIT,
+
+                       MemOE        => MemOE,
+                       MemWR        => MemWR,
+                       RamAdv       => RamAdv,
+                       RamCS        => RamCS,
+                       RamClk       => RamClk,
+                       RamCRE       => RamCRE,
+                       RamLB        => RamLB,
+                       RamUB        => RamUB,
+                       RamWait      => RamWait,
+                       FlashRp      => FlashRp,
+                       FlashCS      => FlashCS,
+                       FlashStSts   => FlashStSts,
+                       MemAdr       => MemAdr,
+                       MemDB        => MemDB,
+
+                       seg          => seg,
+                       dp           => dp,
+                       an           => an,
+                       Led          => Led,
+                       sw           => sw
+               );
+
+
+       ints(2) <= ps2_rx_ready    or
+                  ps2_rx_full     or
+                  ps2_tx_ready    or
+                  ps2_tx_empty    or
+                  ps2_err_nack    or
+                  ps2_err_txto    or
+                  ps2_err_rxto    or
+                  ps2_err_missed  or
+                  ps2_err_parity  or
+                  ps2_err_framing;
+       e_ps2: entity ps2.ps2_host_wb
+               port map (
+                       rst_i       => d_rst,
+                       clk_i       => d_clk,
+
+                       -- Internal access
+                       cyc_i       => ps2_cyc,
+                       stb_i       => stb,
+                       we_i        => we,
+                       ack_o       => ps2_ack,
+                       adr_i       => adr(2 downto 0),
+                       dat_i       => dat_mosi,
+                       dat_o       => ps2_miso,
+
+                       -- Interrupt signals
+                       rx_ready    => ps2_rx_ready,
+                       rx_full     => ps2_rx_full,
+                       tx_ready    => ps2_tx_ready,
+                       tx_empty    => ps2_tx_empty,
+                       err_nack    => ps2_err_nack,
+                       err_txto    => ps2_err_txto,
+                       err_rxto    => ps2_err_rxto,
+                       err_missed  => ps2_err_missed,
+                       err_parity  => ps2_err_parity,
+                       err_framing => ps2_err_framing,
+
+                       -- External pins
+                       ps2_clk     => PS2C,
+                       ps2_data    => PS2D
+               );
+
+
+       ints(3) <= uart_rx_ready     or
+                  uart_rx_full      or
+                  uart_tx_ready     or
+                  uart_tx_empty     or
+                  uart_err_break    or
+                  uart_err_framing  or
+                  uart_err_overflow;
+       e_rs232: entity rs232.rs232_uart_opt
+               port map (
+                       rst_i        => d_rst,
+                       clk_i        => d_clk,
+
+                       -- Internal access
+                       cyc_i        => uart_cyc,
+                       stb_i        => stb,
+                       we_i         => we,
+                       ack_o        => uart_ack,
+                       adr_i        => adr(2 downto 0),
+                       dat_i        => dat_mosi,
+                       dat_o        => uart_miso,
+
+                       -- Interrupt signals
+                       rx_ready     => uart_rx_ready,
+                       rx_full      => uart_rx_full,
+                       tx_ready     => uart_tx_ready,
+                       tx_empty     => uart_tx_empty,
+                       err_break    => uart_err_break,
+                       err_framing  => uart_err_framing,
+                       err_parity   => uart_err_parity,
+                       err_overflow => uart_err_overflow,
+
+                       -- External pins
+                       tx           => RsTx,
+                       rx           => RsRx
+               );
+
+
+       ints(4) <= timer0_zero;
+       e_timer0: entity timer.timer
+               port map (
+                       rst_i => d_rst,
+                       clk_i => d_clk,
+                       cyc_i => timer0_cyc,
+                       stb_i => stb,
+                       we_i  => we,
+                       ack_o => timer0_ack,
+                       adr_i => adr(1 downto 0),
+                       dat_i => dat_mosi,
+                       dat_o => timer0_miso,
+                       zero  => timer0_zero
+               );
+
+
+       ints(5) <= timer1_zero;
+       e_timer1: entity timer.timer
+               port map (
+                       rst_i => d_rst,
+                       clk_i => d_clk,
+                       cyc_i => timer1_cyc,
+                       stb_i => stb,
+                       we_i  => we,
+                       ack_o => timer1_ack,
+                       adr_i => adr(1 downto 0),
+                       dat_i => dat_mosi,
+                       dat_o => timer1_miso,
+                       zero  => timer1_zero
+               );
+
+end behavioral;