OpenCores
URL https://opencores.org/ocsvn/matrix3x3/matrix3x3/trunk

Subversion Repositories matrix3x3

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /
    from Rev 6 to Rev 7
    Reverse comparison

Rev 6 → Rev 7

/trunk/bench/vhdl/multiplier3x3_tb.vhd
0,0 → 1,256
-- ***** BEGIN LICENSE BLOCK *****
----------------------------------------------------------------------
---- ----
---- True matrix 3x3 multiplication IP Core ----
---- ----
---- This file is part of the matrix 3x3 multiplier project ----
---- http://www.opencores.org/projects.cgi/web/matrix3x3/ ----
---- ----
---- Description ----
---- True matrix 3x3 multiplier ----
---- ----
---- To Do: ----
---- - ----
---- ----
---- Author(s): ----
---- - Michael Tsvetkov, michland@opencores.org ----
---- - Vyacheslav Gulyaev, vv_gulyaev@opencores.org ----
---- ----
----------------------------------------------------------------------
---- ----
---- Copyright (C) 2006 Authors and OPENCORES.ORG ----
---- ----
---- This source file may be used and distributed without ----
---- restriction provided that this copyright statement is not ----
---- removed from the file and that any derivative work contains ----
---- the original copyright notice and the associated disclaimer. ----
---- ----
---- This source file is free software; you can redistribute it ----
---- and/or modify it under the terms of the GNU Lesser General ----
---- Public License as published by the Free Software Foundation; ----
---- either version 2.1 of the License, or (at your option) any ----
---- later version. ----
---- ----
---- This source is distributed in the hope that it will be ----
---- useful, but WITHOUT ANY WARRANTY; without even the implied ----
---- warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR ----
---- PURPOSE. See the GNU Lesser General Public License for more ----
---- details. ----
---- ----
---- You should have received a copy of the GNU Lesser General ----
---- Public License along with this source; if not, download it ----
---- from http://www.gnu.org/licenses/lgpl.txt or write to the ----
---- Free Software Foundation, Inc., 51 Franklin Street, ----
---- Fifth Floor, Boston, MA 02110-1301 USA ----
---- ----
----------------------------------------------------------------------
-- * ***** END LICENSE BLOCK ***** */
 
 
-----------------------------------------------------------------------------------
--
-- There is testbench for the myltiplier3x3. Converion realized by multiplication
-- of shifted vectors and matrix of factors, and shift of result of multiplication.
--
-- Input stimulus are read from the "X.txt" file - pure ASCII coded data.
-- Output results are written to the "Y.txt" file - pure ASCII coded data.
-- See Matlab's m-file "read_image.m" in ./fv/ dir for generating input stimulus from
-- the real image.
--
-- Simulator software - ModelSim 6.1.
--
-----------------------------------------------------------------------------------
 
LIBRARY ieee;
LIBRARY std_developerskit;
USE ieee.std_logic_1164.all;
USE std.textio.all;
USE IEEE.std_logic_arith.all;
USE std_developerskit.std_iopak.all;
 
entity tb is
end tb;
 
ARCHITECTURE a OF tb IS
 
CONSTANT DATA_WIDTH : INTEGER :=8;
 
CONSTANT IMAGE_WIDTH : INTEGER := 198;
CONSTANT ROW_NUMBER : INTEGER := 135;
 
CONSTANT CLOCK_PERIOD : TIME := 50 ns;
 
CONSTANT F_FACTORS_PART : INTEGER := 15; -- float part width, 10-E4 accuracy
CONSTANT INT_FACTORS_PART: INTEGER := 3; -- integer part with, from -5 to +4 range (-4.999999 to 3.999999)
CONSTANT FACTORS_WIDTH : integer := (f_factors_part + int_factors_part); -- full factor width
 
 
constant crgb2ycbcr601_a11 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000010000011011111"; -- 0.256789
constant crgb2ycbcr601_a12 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000100000010000110"; -- 0.504129
constant crgb2ycbcr601_a13 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000000110010001000"; -- 0.0979
constant crgb2ycbcr601_a21 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"111110110100000111"; -- -0.148223
constant crgb2ycbcr601_a22 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"111101101011000001"; -- -0.290992
constant crgb2ycbcr601_a23 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000011100000111000"; -- 0.439215
constant crgb2ycbcr601_a31 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000011100000111000"; -- 0.439215
constant crgb2ycbcr601_a32 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"111101000011101100"; -- -0.367789
constant crgb2ycbcr601_a33 : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"111111011011011100"; -- -0.071426
 
constant crgb2ycbcr601_b1x : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000000000000000000"; -- 0
constant crgb2ycbcr601_b2x : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000000000000000000"; -- 0
constant crgb2ycbcr601_b3x : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000000000000000000"; -- 0
 
constant crgb2ycbcr601_b1y : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"000010000000000000"; -- 16
constant crgb2ycbcr601_b2y : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"010000000000000000"; -- 128
constant crgb2ycbcr601_b3y : SIGNED(FACTORS_WIDTH-1 DOWNTO 0) := b"010000000000000000"; -- 128
 
SIGNAL clk : STD_LOGIC;
SIGNAL rstn : STD_LOGIC;
 
SIGNAL x1,x2,x3 : UNSIGNED(DATA_WIDTH-1 DOWNTO 0);
SIGNAL x1bv,x2bv,x3bv : BIT_VECTOR(DATA_WIDTH-1 DOWNTO 0);
 
SIGNAL y1,y2,y3 : UNSIGNED(DATA_WIDTH-1 DOWNTO 0);
SIGNAL y1c,y2c,y3c : SIGNED(INT_FACTORS_PART-1 DOWNTO 0);
SIGNAL y1bv,y2bv,y3bv : BIT_VECTOR(DATA_WIDTH-1 DOWNTO 0);
 
SIGNAL DATA_ENA : STD_LOGIC;
SIGNAL DOUT_RDY : STD_LOGIC;
 
 
BEGIN
 
---------- READ_DATA FROM FILE PROCESS --------------------------
READ_DATA: PROCESS(CLK, RSTN)
FILE file_in : ASCII_TEXT IS "X.txt";
VARIABLE digits_str1 : string(1 to 3);
VARIABLE digits_str2 : string(1 to 3);
VARIABLE digits_str3 : string(1 to 3);
BEGIN
 
if RSTN = '0' THEN
DATA_ENA <= '0';
elsif rising_edge(clk) then
 
if NOT endfile(file_in) THEN
 
fscan (file_in, "%x %x %x", digits_str1, digits_str2, digits_str3);
 
if digits_str1(1) /= NUL then
x1bv <= From_HexString (digits_str1);
x2bv <= From_HexString (digits_str2);
x3bv <= From_HexString (digits_str3);
end if;
 
DATA_ENA <= '1';
 
ELSE
DATA_ENA <= '0';
END IF;
END IF;
 
END PROCESS READ_DATA;
 
 
 
---------- WRITE_RESULT TO FILE PROCESS --------------------------
WRITE_RESULT: PROCESS(CLK, RSTN)
FILE file_out : ASCII_TEXT IS OUT "Y.txt";
VARIABLE digit_out1 : string(1 to 2):=(others=>'0');
VARIABLE digit_out2 : string(1 to 2):=(others=>'0');
VARIABLE digit_out3 : string(1 to 2):=(others=>'0');
VARIABLE i,k : INTEGER;
BEGIN
 
if RSTN = '0' THEN
i := 0;k:=1;
elsif rising_edge(clk) then
if DOUT_RDY = '1' then
if k<=ROW_NUMBER then
i:=i+1;
digit_out1 :=To_string(y1bv,"%2x");
digit_out2 :=To_string(y2bv,"%2x");
digit_out3 :=To_string(y3bv,"%2x");
fprint(file_out,"%s %s %s ", digit_out1, digit_out2, digit_out3);
end if;
if i = IMAGE_WIDTH then
i := 0; k:=k+1;
fprint(file_out,"\n");
end if;
end if;
end if;
END PROCESS WRITE_RESULT;
x1 <= UNSIGNED(TO_STDLOGICVECTOR(x1bv));
x2 <= UNSIGNED(TO_STDLOGICVECTOR(x2bv));
x3 <= UNSIGNED(TO_STDLOGICVECTOR(x3bv));
 
y1bv<=To_Bitvector(STD_LOGIC_VECTOR(y1));
y2bv<=To_Bitvector(STD_LOGIC_VECTOR(y2));
y3bv<=To_Bitvector(STD_LOGIC_VECTOR(y3));
 
--------------------------------------------------------------------
-- instantiate the mult3x3_fullcomponent
--------------------------------------------------------------------
 
mult : entity work.multiplier3x3(a)
GENERIC MAP(
DATA_WIDTH,
F_FACTORS_PART,
INT_FACTORS_PART
)
PORT MAP(
clk => clk,
rstn => rstn,
data_ena => DATA_ENA,
dout_rdy => DOUT_RDY,
x1 => x1,
x2 => x2,
x3 => x3,
a11 => crgb2ycbcr601_a11,
a12 => crgb2ycbcr601_a12,
a13 => crgb2ycbcr601_a13,
a21 => crgb2ycbcr601_a21,
a22 => crgb2ycbcr601_a22,
a23 => crgb2ycbcr601_a23,
a31 => crgb2ycbcr601_a31,
a32 => crgb2ycbcr601_a32,
a33 => crgb2ycbcr601_a33,
b1x => crgb2ycbcr601_b1x,
b2x => crgb2ycbcr601_b2x,
b3x => crgb2ycbcr601_b3x,
b1y => crgb2ycbcr601_b1y,
b2y => crgb2ycbcr601_b2y,
b3y => crgb2ycbcr601_b3y,
y1c => y1c,
y2c => y2c,
y3c => y3c,
y1 => y1,
y2 => y2,
y3 => y3
);
 
--------------------------------------------------------------------
-- clock and reset stuff
--------------------------------------------------------------------
CLOCK : PROCESS
BEGIN
clk <= '1' ;
wait for CLOCK_PERIOD/2;
clk <= '0' ;
wait for CLOCK_PERIOD/2 ;
END PROCESS CLOCK;
RESET : PROCESS
BEGIN
rstn<='0';
wait for 10*CLOCK_PERIOD;
rstn<='1';
wait ;
END PROCESS RESET;
 
END a;
/trunk/rtl/vhdl/multiplier3x3.vhd
0,0 → 1,241
-- ***** BEGIN LICENSE BLOCK *****
----------------------------------------------------------------------
---- ----
---- WISHBONE matrix 3x3 multiplier IP Core ----
---- ----
---- This file is part of the matrix 3x3 multiplier project ----
---- http://www.opencores.org/projects.cgi/web/matrix3x3/ ----
---- ----
---- Description ----
---- Matrix 3x3 multiplier with WISHBONE interface ----
---- ----
---- To Do: ----
---- - ----
---- ----
---- Author(s): ----
---- - Michael Tsvetkov, michland@opencores.org ----
---- - Vyacheslav Gulyaev, vv_gulyaev@opencores.org ----
---- ----
----------------------------------------------------------------------
---- ----
---- Copyright (C) 2007 Authors and OPENCORES.ORG ----
---- ----
---- This source file may be used and distributed without ----
---- restriction provided that this copyright statement is not ----
---- removed from the file and that any derivative work contains ----
---- the original copyright notice and the associated disclaimer. ----
---- ----
---- This source file is free software; you can redistribute it ----
---- and/or modify it under the terms of the GNU Lesser General ----
---- Public License as published by the Free Software Foundation; ----
---- either version 2.1 of the License, or (at your option) any ----
---- later version. ----
---- ----
---- This source is distributed in the hope that it will be ----
---- useful, but WITHOUT ANY WARRANTY; without even the implied ----
---- warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR ----
---- PURPOSE. See the GNU Lesser General Public License for more ----
---- details. ----
---- ----
---- You should have received a copy of the GNU Lesser General ----
---- Public License along with this source; if not, download it ----
---- from http://www.gnu.org/licenses/lgpl.txt ----
---- ----
----------------------------------------------------------------------
-- * ***** END LICENSE BLOCK ***** */
 
library IEEE;
use IEEE.std_logic_1164.all;
use IEEE.std_logic_arith.all;
 
entity multiplier3x3 is
generic(
DATA_WIDTH : INTEGER;
F_FACTORS_PART : INTEGER;
INT_FACTORS_PART : INTEGER
);
 
port (
clk : IN STD_LOGIC;
rstn : IN STD_LOGIC;
 
DATA_ENA : IN STD_LOGIC;
DOUT_RDY : OUT STD_LOGIC;
 
-- input vector
x1 : IN UNSIGNED( data_width-1 downto 0 );
x2 : IN UNSIGNED( data_width-1 downto 0 );
x3 : IN UNSIGNED( data_width-1 downto 0 );
 
-- matrix factors
a11,a12,a13 : IN SIGNED( f_factors_part+int_factors_part-1 downto 0 );
a21,a22,a23 : IN SIGNED( f_factors_part+int_factors_part-1 downto 0 );
a31,a32,a33 : IN SIGNED( f_factors_part+int_factors_part-1 downto 0 );
 
--shift vectors
b1x,b2x,b3x : IN SIGNED( f_factors_part+int_factors_part-1 downto 0 );
b1y,b2y,b3y : IN SIGNED( f_factors_part+int_factors_part-1 downto 0 );
 
-- output vector
y1c : OUT SIGNED( int_factors_part-1 downto 0 );
y2c : OUT SIGNED( int_factors_part-1 downto 0 );
y3c : OUT SIGNED( int_factors_part-1 downto 0 );
y1 : OUT UNSIGNED( data_width-1 downto 0 );
y2 : OUT UNSIGNED( data_width-1 downto 0 );
y3 : OUT UNSIGNED( data_width-1 downto 0 )
);
end multiplier3x3;
 
architecture a of multiplier3x3 is
 
constant factors_width : integer := (f_factors_part + int_factors_part); -- one sign bit
-- the result full width will be
signal m11, m12, m13 : SIGNED( (data_width+factors_width) downto 0 );
signal m21, m22, m23 : SIGNED( (data_width+factors_width) downto 0 );
signal m31, m32, m33 : SIGNED( (data_width+factors_width) downto 0 );
 
signal x1sh, x2sh, x3sh : SIGNED( data_width downto 0 );
 
signal x1s, x2s, x3s : SIGNED( data_width downto 0 );
 
signal y1s, y2s, y3s : SIGNED( data_width+int_factors_part-1 downto 0 );
 
signal y1sh, y2sh, y3sh : SIGNED( data_width+int_factors_part-1 downto 0 );
 
signal y1r, y2r, y3r : SIGNED( data_width+int_factors_part-1 downto 0 );
 
signal y1ro, y2ro, y3ro : SIGNED( data_width+int_factors_part-1 downto 0 );
 
signal s1w, s2w, s3w : SIGNED( (data_width+factors_width) downto 0 );
 
signal d1, d2, d3 : SIGNED( (data_width+factors_width) downto 0 );
 
signal y1w,y2w,y3w : SIGNED( (data_width+factors_width) downto 0 );
 
signal pipe_delay : STD_LOGIC_VECTOR( 7 downto 0 );
 
begin
 
x1s <= '0' & Signed(x1);
x2s <= '0' & Signed(x2);
x3s <= '0' & Signed(x3);
 
process(clk, rstn)
begin
if rstn = '0' then
 
m11 <= (others=>'0');
m12 <= (others=>'0');
m13 <= (others=>'0');
m21 <= (others=>'0');
m22 <= (others=>'0');
m23 <= (others=>'0');
m31 <= (others=>'0');
m32 <= (others=>'0');
m33 <= (others=>'0');
 
s1w <= (others=>'0');
s2w <= (others=>'0');
s3w <= (others=>'0');
 
d1 <= (others=>'0');
d2 <= (others=>'0');
d3 <= (others=>'0');
 
y1w <= (others=>'0');
y2w <= (others=>'0');
y3w <= (others=>'0');
 
y1sh <= (others=>'0');
y2sh <= (others=>'0');
y3sh <= (others=>'0');
 
y1ro <= (others=>'0');
y2ro <= (others=>'0');
y3ro <= (others=>'0');
 
elsif rising_edge(clk) then
 
x1sh <= x1s+b1x(FACTORS_WIDTH-1 DOWNTO FACTORS_WIDTH-DATA_WIDTH-1);
x2sh <= x2s+b2x(FACTORS_WIDTH-1 DOWNTO FACTORS_WIDTH-DATA_WIDTH-1);
x3sh <= x3s+b3x(FACTORS_WIDTH-1 DOWNTO FACTORS_WIDTH-DATA_WIDTH-1);
 
m11 <= a11 * x1sh;
m12 <= a12 * x2sh;
m13 <= a13 * x3sh;
m21 <= a21 * x1sh;
m22 <= a22 * x2sh;
m23 <= a23 * x3sh;
m31 <= a31 * x1sh;
m32 <= a32 * x2sh;
m33 <= a33 * x3sh;
 
s1w <= m11 + m12;
s2w <= m21 + m22;
s3w <= m31 + m32;
 
d1 <= m13;
d2 <= m23;
d3 <= m33;
 
y1w <= s1w + d1;
y2w <= s2w + d2;
y3w <= s3w + d3;
y1s(data_width+int_factors_part-1 downto data_width) <= y1w(data_width+int_factors_part+f_factors_part-1 downto data_width+f_factors_part);
y2s(data_width+int_factors_part-1 downto data_width) <= y2w(data_width+int_factors_part+f_factors_part-1 downto data_width+f_factors_part);
y3s(data_width+int_factors_part-1 downto data_width) <= y3w(data_width+int_factors_part+f_factors_part-1 downto data_width+f_factors_part);
 
y1s(data_width-1 downto 0) <= y1w(data_width+f_factors_part-1 downto f_factors_part);
y2s(data_width-1 downto 0) <= y2w(data_width+f_factors_part-1 downto f_factors_part);
y3s(data_width-1 downto 0) <= y3w(data_width+f_factors_part-1 downto f_factors_part);
 
y1sh <= y1s + b1y(FACTORS_WIDTH-1 DOWNTO FACTORS_WIDTH-DATA_WIDTH-1);
y2sh <= y2s + b2y(FACTORS_WIDTH-1 DOWNTO FACTORS_WIDTH-DATA_WIDTH-1);
y3sh <= y3s + b3y(FACTORS_WIDTH-1 DOWNTO FACTORS_WIDTH-DATA_WIDTH-1);
y1r <= y1sh+y1w(f_factors_part-1);
y2r <= y2sh+y2w(f_factors_part-1);
y3r <= y3sh+y3w(f_factors_part-1);
 
if (y1r(data_width+int_factors_part-1)='1' and y1r(data_width)='1')then y1ro(data_width-1 downto 0)<=(others=>'0');
elsif (y1r(data_width+int_factors_part-1)='0' and y1r(data_width)='1')then y1ro(data_width-1 downto 0)<=(others=>'1');
else y1ro<=y1r;
end if;
 
if (y2r(data_width+int_factors_part-1)='1' and y2r(data_width)='1')then y2ro(data_width-1 downto 0)<=(others=>'0');
elsif (y2r(data_width+int_factors_part-1)='0' and y2r(data_width)='1')then y2ro(data_width-1 downto 0)<=(others=>'1');
else y2ro<=y2r;
end if;
 
if (y3r(data_width+int_factors_part-1)='1' and y3r(data_width)='1')then y3ro(data_width-1 downto 0)<=(others=>'0');
elsif (y3r(data_width+int_factors_part-1)='0' and y3r(data_width)='1')then y3ro(data_width-1 downto 0)<=(others=>'1');
else y3ro<=y3r;
end if;
 
end if;
end process;
 
y1c <= y1r(data_width+int_factors_part-1 downto data_width);
y2c <= y2r(data_width+int_factors_part-1 downto data_width);
y3c <= y3r(data_width+int_factors_part-1 downto data_width);
 
y1 <= UNSIGNED(y1ro(data_width-1 downto 0));
y2 <= UNSIGNED(y2ro(data_width-1 downto 0));
y3 <= UNSIGNED(y3ro(data_width-1 downto 0));
 
-- this shift register is nessecary for generating RDY sig and easy integration with fifo
process(clk, rstn)
begin
if rstn = '0' then
pipe_delay <= (others=>'0');
elsif rising_edge(clk) then
pipe_delay(0) <= DATA_ENA;
pipe_delay(7 downto 1) <= pipe_delay(6 downto 0);
end if;
end process;
 
DOUT_RDY <= pipe_delay(7);
 
 
end a;
/trunk/rtl/vhdl/multiplier3x3_wb.vhd
0,0 → 1,268
-- ***** BEGIN LICENSE BLOCK *****
----------------------------------------------------------------------
---- ----
---- WISHBONE matrix 3x3 multiplier IP Core ----
---- ----
---- This file is part of the matrix 3x3 multiplier project ----
---- http://www.opencores.org/projects.cgi/web/matrix3x3/ ----
---- ----
---- Description ----
---- Matrix 3x3 multiplier with WISHBONE interface ----
---- ----
---- To Do: ----
---- - ----
---- ----
---- Author(s): ----
---- - Michael Tsvetkov, michland@opencores.org ----
---- - Vyacheslav Gulyaev, vv_gulyaev@opencores.org ----
---- ----
----------------------------------------------------------------------
---- ----
---- Copyright (C) 2007 Authors and OPENCORES.ORG ----
---- ----
---- This source file may be used and distributed without ----
---- restriction provided that this copyright statement is not ----
---- removed from the file and that any derivative work contains ----
---- the original copyright notice and the associated disclaimer. ----
---- ----
---- This source file is free software; you can redistribute it ----
---- and/or modify it under the terms of the GNU Lesser General ----
---- Public License as published by the Free Software Foundation; ----
---- either version 2.1 of the License, or (at your option) any ----
---- later version. ----
---- ----
---- This source is distributed in the hope that it will be ----
---- useful, but WITHOUT ANY WARRANTY; without even the implied ----
---- warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR ----
---- PURPOSE. See the GNU Lesser General Public License for more ----
---- details. ----
---- ----
---- You should have received a copy of the GNU Lesser General ----
---- Public License along with this source; if not, download it ----
---- from http://www.gnu.org/licenses/lgpl.txt or write to the ----
---- Free Software Foundation, Inc., 51 Franklin Street, ----
---- Fifth Floor, Boston, MA 02110-1301 USA ----
---- ----
----------------------------------------------------------------------
-- * ***** END LICENSE BLOCK ***** */
 
library IEEE;
use IEEE.std_logic_1164.all;
use IEEE.std_logic_arith.all;
 
entity multiplier3x3_wb is
generic( DATA_WIDTH : INTEGER:=16;
F_FACTORS_PART : INTEGER:= 15;
INT_FACTORS_PART: INTEGER:= 3
);
port (
-- Data Bus (piped stream, our own bus) - x input and y output
x_clk : IN STD_LOGIC;
x_rstn : IN STD_LOGIC;
 
x_we_i : IN STD_LOGIC;
y_rdy_o : OUT STD_LOGIC;
 
-- input vector
x1_i : IN UNSIGNED( data_width-1 downto 0 );
x2_i : IN UNSIGNED( data_width-1 downto 0 );
x3_i : IN UNSIGNED( data_width-1 downto 0 );
-- output vector
y1c_o : OUT SIGNED( int_factors_part-1 downto 0 );
y2c_o : OUT SIGNED( int_factors_part-1 downto 0 );
y3c_o : OUT SIGNED( int_factors_part-1 downto 0 );
 
y1_o : OUT UNSIGNED( data_width-1 downto 0 );
y2_o : OUT UNSIGNED( data_width-1 downto 0 );
y3_o : OUT UNSIGNED( data_width-1 downto 0 );
 
-- Control Bus (WishBone Bus slave) - set factors and shifts regs for mult3x3
wb_clk_i : IN STD_LOGIC;
wb_rst_i : IN STD_LOGIC;
wb_stb_i : IN STD_LOGIC;
wb_we_i : IN STD_LOGIC;
wb_adr_i : IN STD_LOGIC_VECTOR (3 downto 0);
wb_dat_i : IN STD_LOGIC_VECTOR (f_factors_part+int_factors_part-1 downto 0);
wb_dat_o : OUT STD_LOGIC_VECTOR (f_factors_part+int_factors_part-1 downto 0)
);
end multiplier3x3_wb;
 
architecture a of multiplier3x3_wb is
 
constant factors_width : integer := (f_factors_part + int_factors_part); -- one sign bit
--matrix factors
SIGNAL a11 : signed(factors_width-1 downto 0);
SIGNAL a12 : signed(factors_width-1 downto 0);
SIGNAL a13 : signed(factors_width-1 downto 0);
SIGNAL a21 : signed(factors_width-1 downto 0);
SIGNAL a22 : signed(factors_width-1 downto 0);
SIGNAL a23 : signed(factors_width-1 downto 0);
SIGNAL a31 : signed(factors_width-1 downto 0);
SIGNAL a32 : signed(factors_width-1 downto 0);
SIGNAL a33 : signed(factors_width-1 downto 0);
 
--shift vectors
SIGNAL b1x : signed(factors_width-1 downto 0);
SIGNAL b2x : signed(factors_width-1 downto 0);
SIGNAL b3x : signed(factors_width-1 downto 0);
SIGNAL b1y : signed(factors_width-1 downto 0);
SIGNAL b2y : signed(factors_width-1 downto 0);
SIGNAL b3y : signed(factors_width-1 downto 0);
 
COMPONENT multiplier3x3
 
generic( DATA_WIDTH : INTEGER:=8;
F_FACTORS_PART : INTEGER:= 15;
INT_FACTORS_PART: INTEGER:= 3
);
port (
clk : IN STD_LOGIC;
rstn : IN STD_LOGIC;
 
DATA_ENA : IN STD_LOGIC;
DOUT_RDY : OUT STD_LOGIC;
 
-- input vector
x1 : IN UNSIGNED( data_width-1 downto 0 );
x2 : IN UNSIGNED( data_width-1 downto 0 );
x3 : IN UNSIGNED( data_width-1 downto 0 );
 
-- matrix factors
a11,a12,a13 : IN SIGNED( factors_width-1 downto 0 );
a21,a22,a23 : IN SIGNED( factors_width-1 downto 0 );
a31,a32,a33 : IN SIGNED( factors_width-1 downto 0 );
 
--shift vectors
b1x,b2x,b3x : IN SIGNED( factors_width-1 downto 0 );
b1y,b2y,b3y : IN SIGNED( factors_width-1 downto 0 );
-- output vector
y1c : OUT SIGNED( int_factors_part-1 downto 0 );
y2c : OUT SIGNED( int_factors_part-1 downto 0 );
y3c : OUT SIGNED( int_factors_part-1 downto 0 );
 
y1 : OUT UNSIGNED( data_width-1 downto 0 );
y2 : OUT UNSIGNED( data_width-1 downto 0 );
y3 : OUT UNSIGNED( data_width-1 downto 0 )
);
END COMPONENT ;
 
begin
 
-- WB address decoder
process(wb_clk_i, wb_rst_i)
begin
if wb_rst_i='1' then
a11 <= (others=>'0');
a12 <= (others=>'0');
a13 <= (others=>'0');
a21 <= (others=>'0');
a22 <= (others=>'0');
a23 <= (others=>'0');
a31 <= (others=>'0');
a32 <= (others=>'0');
a33 <= (others=>'0');
b1x <= (others=>'0');
b2x <= (others=>'0');
b3x <= (others=>'0');
b1y <= (others=>'0');
b2y <= (others=>'0');
b3y <= (others=>'0');
 
elsif rising_edge(wb_clk_i) then
if wb_stb_i='1' then
if wb_we_i='1' then
 
case wb_adr_i is
when x"0" =>
a11 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"1" =>
a12 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"2" =>
a13 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"3" =>
a21 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"4" =>
a22 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"5" =>
a23 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"6" =>
a31 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"7" =>
a32 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"8" =>
a33 <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"9" =>
b1x <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"A" =>
b2x <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"B" =>
b3x <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"C" =>
b1y <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"D" =>
b2y <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when x"E" =>
b3y <= SIGNED(wb_dat_i(factors_width-1 downto 0));
when others => null;
end case;
 
else
 
case wb_adr_i is
when x"0" =>
wb_dat_o <= STD_LOGIC_VECTOR(a11);
when x"1" =>
wb_dat_o <= STD_LOGIC_VECTOR(a12);
when x"2" =>
wb_dat_o <= STD_LOGIC_VECTOR(a13);
when x"3" =>
wb_dat_o <= STD_LOGIC_VECTOR(a21);
when x"4" =>
wb_dat_o <= STD_LOGIC_VECTOR(a22);
when x"5" =>
wb_dat_o <= STD_LOGIC_VECTOR(a23);
when x"6" =>
wb_dat_o <= STD_LOGIC_VECTOR(a31);
when x"7" =>
wb_dat_o <= STD_LOGIC_VECTOR(a32);
when x"8" =>
wb_dat_o <= STD_LOGIC_VECTOR(a33);
when x"9" =>
wb_dat_o(factors_width-1 downto 0) <= STD_LOGIC_VECTOR(b1x);
when x"A" =>
wb_dat_o(factors_width-1 downto 0) <= STD_LOGIC_VECTOR(b2x);
when x"B" =>
wb_dat_o(factors_width-1 downto 0) <= STD_LOGIC_VECTOR(b3x);
when x"C" =>
wb_dat_o(factors_width-1 downto 0) <= STD_LOGIC_VECTOR(b1y);
when x"D" =>
wb_dat_o(factors_width-1 downto 0) <= STD_LOGIC_VECTOR(b2y);
when x"E" =>
wb_dat_o(factors_width-1 downto 0) <= STD_LOGIC_VECTOR(b3y);
when others => null;
end case;
end if;
end if;
end if;
end process;
 
mult:multiplier3x3
GENERIC MAP(
DATA_WIDTH,
F_FACTORS_PART,
INT_FACTORS_PART
)
PORT MAP (x_clk, x_rstn, x_we_i, y_rdy_o,
x1_i, x2_i, x3_i,
a11, a12, a13,
a21, a22, a23,
a31, a32, a33,
b1x, b2x, b3x,
b1y, b2y, b3y,
y1c_o, y2c_o, y3c_o,
y1_o, y2_o, y3_o
);
end a;
/trunk/doc/multiplier3x3_spec.doc Cannot display: file marked as a binary type. svn:mime-type = application/octet-stream
trunk/doc/multiplier3x3_spec.doc Property changes : Added: svn:mime-type ## -0,0 +1 ## +application/octet-stream \ No newline at end of property Index: trunk/sim/rtl_sim/colorconv_sim.do =================================================================== --- trunk/sim/rtl_sim/colorconv_sim.do (revision 6) +++ trunk/sim/rtl_sim/colorconv_sim.do (nonexistent) @@ -1,43 +0,0 @@ -# -# ModelSim simulation script -# - -# -# project color_conv. -# - -vlib work - -# Compile -vcom -93 -work work ..\\..\\rtl\\vhdl\\ccfactors_pkg.vhd -vcom -93 -work work ..\\..\\rtl\\vhdl\\colorconv.vhd - -vcom -93 -work work ..\\..\\bench\\vhdl\\colorconv_tb.vhd - -#sim -vsim -t ps tb - -########################################################################### -#add wave -noupdate -divider "Color Converter Signals" -add wave -noupdate -format logic /tb/clk -add wave -noupdate -format logic /tb/rstn -add wave -noupdate -format logic /tb/DATA_ENA -add wave -noupdate -format logic /tb/DOUT_RDY -add wave -noupdate -format Literal -radix hexadecimal /tb/x1 -add wave -noupdate -format Literal -radix hexadecimal /tb/x2 -add wave -noupdate -format Literal -radix hexadecimal /tb/x3 -add wave -noupdate -format Literal -radix hexadecimal /tb/y1 -add wave -noupdate -format Literal -radix hexadecimal /tb/y2 -add wave -noupdate -format Literal -radix hexadecimal /tb/y3 - -WaveRestoreZoom {0 us} {10 us} -TreeUpdate [SetDefaultTree] -update - -set RunLength {1400 us} - -run - - - - Index: trunk/sim/rtl_sim/multiplier3x3_sim.do =================================================================== --- trunk/sim/rtl_sim/multiplier3x3_sim.do (nonexistent) +++ trunk/sim/rtl_sim/multiplier3x3_sim.do (revision 7) @@ -0,0 +1,42 @@ +# +# ModelSim simulation script +# + +# +# project color_conv. +# + +vlib work + +# Compile +vcom -93 -work work ..\\..\\rtl\\vhdl\\multiplier3x3.vhd + +vcom -93 -work work ..\\..\\bench\\vhdl\\multiplier3x3_tb.vhd + +#sim +vsim -t ps tb + +########################################################################### +#add wave -noupdate -divider "Color Converter Signals" +add wave -noupdate -format logic /tb/clk +add wave -noupdate -format logic /tb/rstn +add wave -noupdate -format logic /tb/DATA_ENA +add wave -noupdate -format logic /tb/DOUT_RDY +add wave -noupdate -format Literal -radix hexadecimal /tb/x1 +add wave -noupdate -format Literal -radix hexadecimal /tb/x2 +add wave -noupdate -format Literal -radix hexadecimal /tb/x3 +add wave -noupdate -format Literal -radix hexadecimal /tb/y1 +add wave -noupdate -format Literal -radix hexadecimal /tb/y2 +add wave -noupdate -format Literal -radix hexadecimal /tb/y3 + +WaveRestoreZoom {0 us} {10 us} +TreeUpdate [SetDefaultTree] +update + +set RunLength {1400 us} + +run + + + +

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.