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

Subversion Repositories mod_mult_exp

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /mod_mult_exp
    from Rev 2 to Rev 3
    Reverse comparison

Rev 2 → Rev 3

/trunk/bench/vhdl/mod_mult/ModularMultiplierIterative32bitTB.vhd
0,0 → 1,182
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- This is TestBench for the Montgomery modular multiplier ----
---- with the 64 bit width. ----
---- it takes two nubers and modulus as the input and results ----
---- the Montgomery product A*B*(R^{-1}) mod M ----
---- where R^{-1} is the modular multiplicative inverse. ----
---- R*R^{-1} == 1 mod M ----
---- R = 2^word_length mod M ----
---- and word_length is the binary width of the ----
---- operated word (in this case 64 bit) ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
-- Uncomment the following library declaration if using
-- arithmetic functions with Signed or Unsigned values
--USE ieee.numeric_std.ALL;
ENTITY ModularMultiplierIterative32bitTB IS
END ModularMultiplierIterative32bitTB;
ARCHITECTURE behavior OF ModularMultiplierIterative32bitTB IS
-- Component Declaration for the Unit Under Test (UUT)
COMPONENT ModularMultiplierIterative
PORT(
A : IN STD_LOGIC_VECTOR(31 downto 0);
B : IN STD_LOGIC_VECTOR(31 downto 0);
M : IN STD_LOGIC_VECTOR(31 downto 0);
start : IN STD_LOGIC;
product : OUT STD_LOGIC_VECTOR(31 downto 0);
ready : OUT STD_LOGIC;
clk : IN STD_LOGIC
);
END COMPONENT;
 
--Inputs
signal A : STD_LOGIC_VECTOR(31 downto 0) := (others => '0');
signal B : STD_LOGIC_VECTOR(31 downto 0) := (others => '0');
signal M : STD_LOGIC_VECTOR(31 downto 0) := (others => '0');
signal start : STD_LOGIC := '0';
signal clk : STD_LOGIC := '0';
 
--Outputs
signal product : std_logic_vector(31 downto 0);
signal ready : STD_LOGIC;
 
-- Clock period definitions
constant clk_period : time := 10 ns;
BEGIN
-- Instantiate the Unit Under Test (UUT)
uut: ModularMultiplierIterative PORT MAP (
A => A,
B => B,
M => M,
start => start,
product => product,
ready => ready,
clk => clk
);
 
-- Clock process definitions
clk_process :process
begin
clk <= '0';
wait for clk_period/2;
clk <= '1';
wait for clk_period/2;
end process;
 
-- Stimulus process
stim_proc: process
begin
-- hold reset state for 100 ns.
start <= '0';
wait for 100 ns;
 
---- Preparation for test case 1 -----------------
-- A = 1073741827 in decimal
-- B = 1876543287 in decimal
-- M = 2147483659 in decimal
-- expected_result = 1075674849379283795 in decimal, in hex 66e4624e
-- mod(1073741827*1876543287*1659419191, 2147483659) = 1726243406
-- where 2703402148733296366 is the inverse modulus
--------------------------------------------------
start <= '1';
-- A = 1073741827 in decimal
A <= "01000000000000000000000000000011";
-- B = 1876543210987 in decimal
B <= "01101111110110011100011100110111";
-- M = 2147483659 in decimal
M <= "10000000000000000000000000001011";
--wait for 80*clk_period;
wait until ready = '1' and clk = '0';
if product /= x"66e4624e" then
report "RESULT MISMATCH! Test case 1 failed" severity ERROR;
assert false severity failure;
else
report "Test case 1 successful" severity note;
end if;
 
start <= '0';
---- Preparation for test case 2 -----------------
-- A = 1073741826 in decimal
-- B = 1876543286 in decimal
-- M = 2147483659 in decimal
-- expected_result = 1075674849379283795 in decimal, in hex 66e4624e
-- mod(1073741826*1876543286*1659419191, 2147483659) = 1567508594
-- where 1659419191 is the inverse modulus
--------------------------------------------------
 
-- A = 1073741826 in decimal
A <= "01000000000000000000000000000010";
-- B = 1876543210986 in decimal
B <= "01101111110110011100011100110110";
-- M = 2147483659 in decimal
M <= "10000000000000000000000000001011";
wait for clk_period;
start <= '1';
--wait for 80*clk_period;
wait until ready = '1' and clk = '0';
if product /= x"5d6e4872" then
report "RESULT MISMATCH! Test case 2 failed" severity ERROR;
assert false severity failure;
else
report "Test case 2 successful" severity note;
end if;
assert false severity failure;
end process;
 
END;
/trunk/bench/vhdl/mod_mult/ModularMultiplierIterative512bitTB.vhd
0,0 → 1,197
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- This is TestBench for the Montgomery modular multiplier ----
---- with the 512 bit width. ----
---- it takes two nubers and modulus as the input and results ----
---- the Montgomery product A*B*(R^{-1}) mod M ----
---- where R^{-1} is the modular multiplicative inverse. ----
---- R*R^{-1} == 1 mod M ----
---- R = 2^word_length mod M ----
---- and word_length is the binary width of the ----
---- operated word (in this case 512 bit) ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
-- Uncomment the following library declaration if using
-- arithmetic functions with Signed or Unsigned values
--USE ieee.numeric_std.ALL;
ENTITY ModularMultiplierIterative512bitTB IS
END ModularMultiplierIterative512bitTB;
ARCHITECTURE behavior OF ModularMultiplierIterative512bitTB IS
-- Component Declaration for the Unit Under Test (UUT)
COMPONENT ModularMultiplierIterative
PORT(
A : in STD_LOGIC_VECTOR(511 downto 0);
B : in STD_LOGIC_VECTOR(511 downto 0);
M : in STD_LOGIC_VECTOR(511 downto 0);
start : in STD_LOGIC;
product : out STD_LOGIC_VECTOR(511 downto 0);
ready : out STD_LOGIC;
clk : in STD_LOGIC
);
END COMPONENT;
 
--Inputs
signal A : STD_LOGIC_VECTOR(511 downto 0) := (others => '0');
signal B : STD_LOGIC_VECTOR(511 downto 0) := (others => '0');
signal M : STD_LOGIC_VECTOR(511 downto 0) := (others => '0');
signal start : STD_LOGIC := '0';
signal clk : STD_LOGIC := '0';
 
--Outputs
signal product : STD_LOGIC_VECTOR(511 downto 0);
signal ready : STD_LOGIC;
 
-- Clock period definitions
constant clk_period : time := 10 ns;
BEGIN
-- Instantiate the Unit Under Test (UUT)
uut: ModularMultiplierIterative PORT MAP (
A => A,
B => B,
M => M,
start => start,
product => product,
ready => ready,
clk => clk
);
 
-- Clock process definitions
clk_process :process
begin
clk <= '0';
wait for clk_period/2;
clk <= '1';
wait for clk_period/2;
end process;
 
-- Stimulus process
stim_proc: process
begin
-- hold reset state for 100 ns.
start <= '0';
wait for 100 ns;
 
---- Preparation for test case 1 -----------------
-- A = 1135574785903187283000914738069914842639275616893687122668359807022003618585980215260939798952644749528921700342000274265548842002316414917974647561961683 in decimal
-- B = 97927786390663519429528993360368267006249228136794892056090651513080073109454331808866772457049032741774590681339704155886317906072752116837364369820881 in decimal
-- M = 3351951982485649274893506249551461531869841455148098344430890360930446855046914914263767984168972974033957028381338463851007479808527777429670210341401251 in decimal
-- expected_result = 2228133496571818711622350692880669459929128102839647013792122413518929533298354919965858625663488002993791315812426542313874032336596139553001249634708855 in decimal,
-- in hex 2a8ae3c12ae96d6babce2e342ec7beeff5754a14e7c8e6057eeebf6dc1cb12145e26e97c874f8e05cfa6fcaf83240f90d2fd21b3f41016b74607c143e49eed77
-- mod(
-- 1135574785903187283000914738069914842639275616893687122668359807022003618585980215260939798952644749528921700342000274265548842002316414917974647561961683 *
-- 97927786390663519429528993360368267006249228136794892056090651513080073109454331808866772457049032741774590681339704155886317906072752116837364369820881 *
-- 2591367877621154684380773880291249237701602230100736077754314629198930824379666744084279080961590867282481555124997788427853751639203524473059719065731751 ,
-- 3351951982485649274893506249551461531869841455148098344430890360930446855046914914263767984168972974033957028381338463851007479808527777429670210341401251 ) =
-- = 2228133496571818711622350692880669459929128102839647013792122413518929533298354919965858625663488002993791315812426542313874032336596139553001249634708855
-- where 2591367877621154684380773880291249237701602230100736077754314629198930824379666744084279080961590867282481555124997788427853751639203524473059719065731751 is the inverse modulus
--------------------------------------------------
start <= '1';
-- A = 1135574785903187283000914738069914842639275616893687122668359807022003618585980215260939798952644749528921700342000274265548842002316414917974647561961683 in decimal
A <= "00010101101011101001001011101101001001011100110110111011001010010100010110000100000101001010110100011010001010001111101000110101111101011011111111000011000100011101011111100001111011111110110110111010011101010011111001001000110011001110111000011110100111111111000111010001011000000111000101000100010010011011111101101111100001011010000011100011111111100000011110000100010101001000101100111100010001100001101011000101111110111111001010001011011110100001110000111100100000111111010011011111111101101100000011010011";
-- B = 97927786390663519429528993360368267006249228136794892056090651513080073109454331808866772457049032741774590681339704155886317906072752116837364369820881 in decimal
B <= "00000001110111101010100100111010100000100100111111101001100100111011001111000010101011111001001001110011011010010100101000100010110011011101111000010011100100101000011010000110110010101101101100000111101000001111010101000110100001100011101110100011100111101100000001000110010110111001110111111110101000001110001000011001000001000000111100000001100110000100011100010011101110010100111110010111110001000110111010010010101101001111110000111001110000100111111111100011011101100000011110100100100000011000110011010001";
-- M = 3351951982485649274893506249551461531869841455148098344430890360930446855046914914263767984168972974033957028381338463851007479808527777429670210341401251 in decimal
M <= "01000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000110000001010010010100100100000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000010110101111001111111011110110110111001010100011";
--wait for 600*clk_period;
-- Result = 2228133496571818711622350692880669459929128102839647013792122413518929533298354919965858625663488002993791315812426542313874032336596139553001249634708855 in decimal
wait until ready = '1' and clk = '0';
if product /= x"2a8ae3c12ae96d6babce2e342ec7beeff5754a14e7c8e6057eeebf6dc1cb12145e26e97c874f8e05cfa6fcaf83240f90d2fd21b3f41016b74607c143e49eed77" then
report "RESULT MISMATCH! Test case 1 failed" severity ERROR;
assert false severity failure;
else
report "Test case 1 successful" severity note;
end if;
start <= '0';
 
---- Preparation for test case 2 -----------------
-- A = 3351951982485649274893506249551461531869841455148098344430890360930441007518386744200468574541725856922507964546621512713438470702986642486608412251521039 in decimal
-- B = 97927786390663519429528993360368267006249228136794892056090651513080073109454331808866772457049032741774590681339704155886317906072752116837364369820881 in decimal
-- M = 6703903964971298549787012499102923063739682910296196688861780721860882015036773488400937149083451713845015929093243025426876941405973284973216824503042159 in decimal
-- expected_result = 5770539552593938046267215339235143056108840937616962443047031076129629580294766891795665005337423591502330655021878623252853392851503861478061794255888635 in decimal,
-- in hex 6e2dcf4e2226cb7a14afa007b0bafdf50d573776681c0cca8d7ff56515076baffd05eaa8ee73d63874a1df6d13e2bbc0aeb6dcd21d8ee10613df1e2e5e02e0fb
-- mod(
-- 3351951982485649274893506249551461531869841455148098344430890360930441007518386744200468574541725856922507964546621512713438470702986642486608412251521039 *
-- 97927786390663519429528993360368267006249228136794892056090651513080073109454331808866772457049032741774590681339704155886317906072752116837364369820881 *
-- 6311333012067573859934619875281580722169341118251824810685189958869028563705791257098179568281267604475713194506701767181158922314632507024334758203314465 ,
-- 6703903964971298549787012499102923063739682910296196688861780721860882015036773488400937149083451713845015929093243025426876941405973284973216824503042159 ) =
-- = 5770539552593938046267215339235143056108840937616962443047031076129629580294766891795665005337423591502330655021878623252853392851503861478061794255888635
-- where 6311333012067573859934619875281580722169341118251824810685189958869028563705791257098179568281267604475713194506701767181158922314632507024334758203314465 is the inverse modulus
--------------------------------------------------
 
-- A = 3351951982485649274893506249551461531869841455148098344430890360930441007518386744200468574541725856922507964546621512713438470702986642486608412251521039 in decimal
A <= "01000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001111";
-- B = 97927786390663519429528993360368267006249228136794892056090651513080073109454331808866772457049032741774590681339704155886317906072752116837364369820881 in decimal
B <= "00000001110111101010100100111010100000100100111111101001100100111011001111000010101011111001001001110011011010010100101000100010110011011101111000010011100100101000011010000110110010101101101100000111101000001111010101000110100001100011101110100011100111101100000001000110010110111001110111111110101000001110001000011001000001000000111100000001100110000100011100010011101110010100111110010111110001000110111010010010101101001111110000111001110000100111111111100011011101100000011110100100100000011000110011010001";
-- M = 6703903964971298549787012499102923063739682910296196688861780721860882015036773488400937149083451713845015929093243025426876941405973284973216824503042159 in decimal
M <= "10000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000001101111";
wait for clk_period;
-- Result = 1075674849379283795 in decimal
start <= '1';
--wait for 600*clk_period;
wait until ready = '1' and clk = '0';
if product /= x"6e2dcf4e2226cb7a14afa007b0bafdf50d573776681c0cca8d7ff56515076baffd05eaa8ee73d63874a1df6d13e2bbc0aeb6dcd21d8ee10613df1e2e5e02e0fb" then
report "RESULT MISMATCH! Test case 2 failed" severity ERROR;
assert false severity failure;
else
report "Test case 2 successful" severity note;
end if;
assert false severity failure;
end process;
 
END;
/trunk/bench/vhdl/mod_mult/ModularMultiplierIterative64bitTB.vhd
0,0 → 1,183
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- This is TestBench for the Montgomery modular multiplier ----
---- with the 64 bit width. ----
---- it takes two nubers and modulus as the input and results ----
---- the Montgomery product A*B*(R^{-1}) mod M ----
---- where R^{-1} is the modular multiplicative inverse. ----
---- R*R^{-1} == 1 mod M ----
---- R = 2^word_length mod M ----
---- and word_length is the binary width of the ----
---- operated word (in this case 64 bit) ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
-- Uncomment the following library declaration if using
-- arithmetic functions with Signed or Unsigned values
--USE ieee.numeric_std.ALL;
ENTITY ModularMultiplierIterative64bitTB IS
END ModularMultiplierIterative64bitTB;
ARCHITECTURE behavior OF ModularMultiplierIterative64bitTB IS
-- Component Declaration for the Unit Under Test (UUT)
COMPONENT ModularMultiplierIterative
PORT(
A : IN STD_LOGIC_VECTOR(63 downto 0);
B : IN STD_LOGIC_VECTOR(63 downto 0);
M : IN STD_LOGIC_VECTOR(63 downto 0);
start : IN STD_LOGIC;
product : OUT STD_LOGIC_VECTOR(63 downto 0);
ready : OUT STD_LOGIC;
clk : IN STD_LOGIC
);
END COMPONENT;
 
--Inputs
signal A : STD_LOGIC_VECTOR(63 downto 0) := (others => '0');
signal B : STD_LOGIC_VECTOR(63 downto 0) := (others => '0');
signal M : STD_LOGIC_VECTOR(63 downto 0) := (others => '0');
signal start : STD_LOGIC := '0';
signal clk : STD_LOGIC := '0';
 
--Outputs
signal product : std_logic_vector(63 downto 0);
signal ready : STD_LOGIC;
 
-- Clock period definitions
constant clk_period : time := 10 ns;
BEGIN
-- Instantiate the Unit Under Test (UUT)
uut: ModularMultiplierIterative PORT MAP (
A => A,
B => B,
M => M,
start => start,
product => product,
ready => ready,
clk => clk
);
 
-- Clock process definitions
clk_process :process
begin
clk <= '0';
wait for clk_period/2;
clk <= '1';
wait for clk_period/2;
end process;
 
-- Stimulus process
stim_proc: process
begin
-- hold reset state for 100 ns.
start <= '0';
wait for 100 ns;
 
---- Preparation for test case 1 -----------------
-- A = 1234567890123 in decimal
-- B = 9876543210987 in decimal
-- M = 9223372036854775837 in decimal
-- expected_result = 1075674849379283795 in decimal, in hex
-- mod(1234567890123*9876543210987*2703402148733296366, 9223372036854775837) = 1075674849379283795
-- where 2703402148733296366 is the inverse modulus
--------------------------------------------------
start <= '1';
-- A = 1234567890123 in decimal
A <= "0000000000000000000000010001111101110001111110110000010011001011";
-- B = 9876543210987 in decimal
B <= "0000000000000000000010001111101110001111110110011000010111101011";
-- M = 9223372036854775837 in decimal
M <= "1000000000000000000000000000000000000000000000000000000000011101";
--wait for 80*clk_period;
wait until ready = '1' and clk = '0';
if product /= x"0eed90938b12f353" then
report "RESULT MISMATCH! Test case 1 failed" severity ERROR;
assert false severity failure;
else
report "Test case 1 successful" severity note;
end if;
 
---- Preparation for test case 2 -----------------
-- A = 2405361651273580285 in decimal
-- B = 1851187696912577658 in decimal
-- M = 4612794175830006917 in decimal
-- expected_result = 1075674849379283795 in decimal
-- mod(2405361651273580285*1851187696912577658*377014635792245467, 4612794175830006917) = 1424433616378222832
-- where 377014635792245467 is the inverse modulus
--------------------------------------------------
 
 
start <= '0';
-- A = 2405361651273580285
A <= "0010000101100001100011111010110101111100100000100011111011111101";
-- B = 1851187696912577658
B <= "0001100110110000101111010110011011111111000011000011010001111010";
-- M = 4612794175830006917
M <= "0100000000000011111011111101110100000000010101101001110010000101";
wait for clk_period;
start <= '1';
--wait for 80*clk_period;
wait until ready = '1' and clk = '0';
if product /= x"13c49ad3be5958f0" then
report "RESULT MISMATCH! Test case 2 failed" severity ERROR;
assert false severity failure;
else
report "Test case 2 successful" severity note;
end if;
assert false severity failure;
end process;
 
END;
/trunk/bench/vhdl/txt_util.vhd
0,0 → 1,586
library ieee;
use ieee.std_logic_1164.all;
use std.textio.all;
 
 
package txt_util is
 
-- prints a message to the screen
procedure print(text: string);
 
-- prints the message when active
-- useful for debug switches
procedure print(active: boolean; text: string);
 
-- converts std_logic into a character
function chr(sl: std_logic) return character;
 
-- converts std_logic into a string (1 to 1)
function str(sl: std_logic) return string;
 
-- converts std_logic_vector into a string (binary base)
function str(slv: std_logic_vector) return string;
 
-- converts boolean into a string
function str(b: boolean) return string;
 
-- converts an integer into a single character
-- (can also be used for hex conversion and other bases)
function chr(int: integer) return character;
 
-- converts integer into string using specified base
function str(int: integer; base: integer) return string;
 
-- converts integer to string, using base 10
function str(int: integer) return string;
 
-- convert std_logic_vector into a string in hex format
function hstr(slv: std_logic_vector) return string;
 
 
-- functions to manipulate strings
-----------------------------------
 
-- convert a character to upper case
function to_upper(c: character) return character;
 
-- convert a character to lower case
function to_lower(c: character) return character;
 
-- convert a string to upper case
function to_upper(s: string) return string;
 
-- convert a string to lower case
function to_lower(s: string) return string;
 
-- functions to convert strings into other formats
--------------------------------------------------
-- converts a character into std_logic
function to_std_logic(c: character) return std_logic;
-- converts a string into std_logic_vector
function to_std_logic_vector(s: string) return std_logic_vector;
 
 
-- file I/O
-----------
-- read variable length string from input file
procedure str_read(file in_file: TEXT;
res_string: out string);
-- print string to a file and start new line
procedure print(file out_file: TEXT;
new_string: in string);
-- print character to a file and start new line
procedure print(file out_file: TEXT;
char: in character);
end txt_util;
 
 
 
 
package body txt_util is
 
 
 
 
-- prints text to the screen
 
procedure print(text: string) is
variable msg_line: line;
begin
write(msg_line, text);
writeline(output, msg_line);
end print;
 
 
 
 
-- prints text to the screen when active
 
procedure print(active: boolean; text: string) is
begin
if active then
print(text);
end if;
end print;
 
 
-- converts std_logic into a character
 
function chr(sl: std_logic) return character is
variable c: character;
begin
case sl is
when 'U' => c:= 'U';
when 'X' => c:= 'X';
when '0' => c:= '0';
when '1' => c:= '1';
when 'Z' => c:= 'Z';
when 'W' => c:= 'W';
when 'L' => c:= 'L';
when 'H' => c:= 'H';
when '-' => c:= '-';
end case;
return c;
end chr;
 
 
 
-- converts std_logic into a string (1 to 1)
 
function str(sl: std_logic) return string is
variable s: string(1 to 1);
begin
s(1) := chr(sl);
return s;
end str;
 
 
 
-- converts std_logic_vector into a string (binary base)
-- (this also takes care of the fact that the range of
-- a string is natural while a std_logic_vector may
-- have an integer range)
 
function str(slv: std_logic_vector) return string is
variable result : string (1 to slv'length);
variable r : integer;
begin
r := 1;
for i in slv'range loop
result(r) := chr(slv(i));
r := r + 1;
end loop;
return result;
end str;
 
 
function str(b: boolean) return string is
 
begin
if b then
return "true";
else
return "false";
end if;
end str;
 
 
-- converts an integer into a character
-- for 0 to 9 the obvious mapping is used, higher
-- values are mapped to the characters A-Z
-- (this is usefull for systems with base > 10)
-- (adapted from Steve Vogwell's posting in comp.lang.vhdl)
 
function chr(int: integer) return character is
variable c: character;
begin
case int is
when 0 => c := '0';
when 1 => c := '1';
when 2 => c := '2';
when 3 => c := '3';
when 4 => c := '4';
when 5 => c := '5';
when 6 => c := '6';
when 7 => c := '7';
when 8 => c := '8';
when 9 => c := '9';
when 10 => c := 'A';
when 11 => c := 'B';
when 12 => c := 'C';
when 13 => c := 'D';
when 14 => c := 'E';
when 15 => c := 'F';
when 16 => c := 'G';
when 17 => c := 'H';
when 18 => c := 'I';
when 19 => c := 'J';
when 20 => c := 'K';
when 21 => c := 'L';
when 22 => c := 'M';
when 23 => c := 'N';
when 24 => c := 'O';
when 25 => c := 'P';
when 26 => c := 'Q';
when 27 => c := 'R';
when 28 => c := 'S';
when 29 => c := 'T';
when 30 => c := 'U';
when 31 => c := 'V';
when 32 => c := 'W';
when 33 => c := 'X';
when 34 => c := 'Y';
when 35 => c := 'Z';
when others => c := '?';
end case;
return c;
end chr;
 
 
 
-- convert integer to string using specified base
-- (adapted from Steve Vogwell's posting in comp.lang.vhdl)
 
function str(int: integer; base: integer) return string is
 
variable temp: string(1 to 10);
variable num: integer;
variable abs_int: integer;
variable len: integer := 1;
variable power: integer := 1;
 
begin
 
-- bug fix for negative numbers
abs_int := abs(int);
 
num := abs_int;
 
while num >= base loop -- Determine how many
len := len + 1; -- characters required
num := num / base; -- to represent the
end loop ; -- number.
 
for i in len downto 1 loop -- Convert the number to
temp(i) := chr(abs_int/power mod base); -- a string starting
power := power * base; -- with the right hand
end loop ; -- side.
 
-- return result and add sign if required
if int < 0 then
return '-'& temp(1 to len);
else
return temp(1 to len);
end if;
 
end str;
 
 
-- convert integer to string, using base 10
function str(int: integer) return string is
 
begin
 
return str(int, 10) ;
 
end str;
 
 
 
-- converts a std_logic_vector into a hex string.
function hstr(slv: std_logic_vector) return string is
variable hexlen: integer;
variable longslv : std_logic_vector(67 downto 0) := (others => '0');
variable hex : string(1 to 16);
variable fourbit : std_logic_vector(3 downto 0);
begin
hexlen := (slv'left+1)/4;
if (slv'left+1) mod 4 /= 0 then
hexlen := hexlen + 1;
end if;
longslv(slv'left downto 0) := slv;
for i in (hexlen -1) downto 0 loop
fourbit := longslv(((i*4)+3) downto (i*4));
case fourbit is
when "0000" => hex(hexlen -I) := '0';
when "0001" => hex(hexlen -I) := '1';
when "0010" => hex(hexlen -I) := '2';
when "0011" => hex(hexlen -I) := '3';
when "0100" => hex(hexlen -I) := '4';
when "0101" => hex(hexlen -I) := '5';
when "0110" => hex(hexlen -I) := '6';
when "0111" => hex(hexlen -I) := '7';
when "1000" => hex(hexlen -I) := '8';
when "1001" => hex(hexlen -I) := '9';
when "1010" => hex(hexlen -I) := 'A';
when "1011" => hex(hexlen -I) := 'B';
when "1100" => hex(hexlen -I) := 'C';
when "1101" => hex(hexlen -I) := 'D';
when "1110" => hex(hexlen -I) := 'E';
when "1111" => hex(hexlen -I) := 'F';
when "ZZZZ" => hex(hexlen -I) := 'z';
when "UUUU" => hex(hexlen -I) := 'u';
when "XXXX" => hex(hexlen -I) := 'x';
when others => hex(hexlen -I) := '?';
end case;
end loop;
return hex(1 to hexlen);
end hstr;
 
 
 
-- functions to manipulate strings
-----------------------------------
 
 
-- convert a character to upper case
 
function to_upper(c: character) return character is
 
variable u: character;
 
begin
 
case c is
when 'a' => u := 'A';
when 'b' => u := 'B';
when 'c' => u := 'C';
when 'd' => u := 'D';
when 'e' => u := 'E';
when 'f' => u := 'F';
when 'g' => u := 'G';
when 'h' => u := 'H';
when 'i' => u := 'I';
when 'j' => u := 'J';
when 'k' => u := 'K';
when 'l' => u := 'L';
when 'm' => u := 'M';
when 'n' => u := 'N';
when 'o' => u := 'O';
when 'p' => u := 'P';
when 'q' => u := 'Q';
when 'r' => u := 'R';
when 's' => u := 'S';
when 't' => u := 'T';
when 'u' => u := 'U';
when 'v' => u := 'V';
when 'w' => u := 'W';
when 'x' => u := 'X';
when 'y' => u := 'Y';
when 'z' => u := 'Z';
when others => u := c;
end case;
 
return u;
 
end to_upper;
 
 
-- convert a character to lower case
 
function to_lower(c: character) return character is
 
variable l: character;
 
begin
 
case c is
when 'A' => l := 'a';
when 'B' => l := 'b';
when 'C' => l := 'c';
when 'D' => l := 'd';
when 'E' => l := 'e';
when 'F' => l := 'f';
when 'G' => l := 'g';
when 'H' => l := 'h';
when 'I' => l := 'i';
when 'J' => l := 'j';
when 'K' => l := 'k';
when 'L' => l := 'l';
when 'M' => l := 'm';
when 'N' => l := 'n';
when 'O' => l := 'o';
when 'P' => l := 'p';
when 'Q' => l := 'q';
when 'R' => l := 'r';
when 'S' => l := 's';
when 'T' => l := 't';
when 'U' => l := 'u';
when 'V' => l := 'v';
when 'W' => l := 'w';
when 'X' => l := 'x';
when 'Y' => l := 'y';
when 'Z' => l := 'z';
when others => l := c;
end case;
 
return l;
 
end to_lower;
 
 
 
-- convert a string to upper case
 
function to_upper(s: string) return string is
 
variable uppercase: string (s'range);
 
begin
 
for i in s'range loop
uppercase(i):= to_upper(s(i));
end loop;
return uppercase;
 
end to_upper;
 
 
 
-- convert a string to lower case
 
function to_lower(s: string) return string is
 
variable lowercase: string (s'range);
 
begin
 
for i in s'range loop
lowercase(i):= to_lower(s(i));
end loop;
return lowercase;
 
end to_lower;
 
 
 
-- functions to convert strings into other types
 
 
-- converts a character into a std_logic
 
function to_std_logic(c: character) return std_logic is
variable sl: std_logic;
begin
case c is
when 'U' =>
sl := 'U';
when 'X' =>
sl := 'X';
when '0' =>
sl := '0';
when '1' =>
sl := '1';
when 'Z' =>
sl := 'Z';
when 'W' =>
sl := 'W';
when 'L' =>
sl := 'L';
when 'H' =>
sl := 'H';
when '-' =>
sl := '-';
when others =>
sl := 'X';
end case;
return sl;
end to_std_logic;
 
 
-- converts a string into std_logic_vector
 
function to_std_logic_vector(s: string) return std_logic_vector is
variable slv: std_logic_vector(s'high-s'low downto 0);
variable k: integer;
begin
k := s'high-s'low;
for i in s'range loop
slv(k) := to_std_logic(s(i));
k := k - 1;
end loop;
return slv;
end to_std_logic_vector;
----------------
-- file I/O --
----------------
 
 
 
-- read variable length string from input file
procedure str_read(file in_file: TEXT;
res_string: out string) is
variable l: line;
variable c: character;
variable is_string: boolean;
begin
readline(in_file, l);
-- clear the contents of the result string
for i in res_string'range loop
res_string(i) := ' ';
end loop;
-- read all characters of the line, up to the length
-- of the results string
for i in res_string'range loop
read(l, c, is_string);
res_string(i) := c;
if not is_string then -- found end of line
exit;
end if;
end loop;
end str_read;
 
 
-- print string to a file
procedure print(file out_file: TEXT;
new_string: in string) is
variable l: line;
begin
write(l, new_string);
writeline(out_file, l);
end print;
 
 
-- print character to a file and start new line
procedure print(file out_file: TEXT;
char: in character) is
variable l: line;
begin
write(l, char);
writeline(out_file, l);
end print;
 
 
 
-- appends contents of a string to a file until line feed occurs
-- (LF is considered to be the end of the string)
 
procedure str_write(file out_file: TEXT;
new_string: in string) is
begin
for i in new_string'range loop
print(out_file, new_string(i));
if new_string(i) = LF then -- end of string
exit;
end if;
end loop;
end str_write;
 
 
 
 
end txt_util;
 
 
 
 
/trunk/rtl/vhdl/mod_mult/ModMultIter_SM.vhd
0,0 → 1,166
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- This is state machine for the modular multiplier it consists----
---- of three states, NOP the preparation stage, CALCULATE_START ----
---- for the modular multiply and STOP for the presentation ----
---- result. ----
---- ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.STD_LOGIC_UNSIGNED.ALL;
use work.properties.ALL;
 
-- Uncomment the following library declaration if using
-- arithmetic functions with Signed or Unsigned values
--use IEEE.NUMERIC_STD.ALL;
 
-- Uncomment the following library declaration if instantiating
-- any Xilinx primitives in this code.
--library UNISIM;
--use UNISIM.VComponents.all;
 
entity ModMultIter_SM is
generic (
word_size : integer := WORD_LENGTH;
word_binary : integer := WORD_INTEGER
);
port(
x : in STD_LOGIC_VECTOR(word_size - 1 downto 0);
start : in STD_LOGIC;
clk : in STD_LOGIC;
s_0 : in STD_LOGIC;
y_0 : in STD_LOGIC;
ready : out STD_LOGIC;
out_reg_en : out STD_LOGIC;
mux_mult_ctrl : out STD_LOGIC;
mux_4in_ctrl : out STD_LOGIC_VECTOR(1 downto 0)
);
end ModMultIter_SM;
 
architecture Behavioral of ModMultIter_SM is
 
signal state : multiplier_states := NOP;
signal next_state : multiplier_states := NOP;
signal position_counter : STD_LOGIC_VECTOR(word_binary downto 0) := (others => '0');
signal shift_reg : STD_LOGIC_VECTOR(word_size - 1 downto 0) := (others => '0');
 
signal q : STD_LOGIC;
 
begin
q <= (shift_reg(0) and y_0) xor s_0;
mux_4in_ctrl <= shift_reg(0) & q;
SM : process(state, start, position_counter)
begin
case state is
-- Prepare for the Montgomery iterations
when NOP =>
ready <= '0';
if (start = '1') then
next_state <= CALCULATE_START;
out_reg_en <= '1';
mux_mult_ctrl <= '1';
else
out_reg_en <= '0';
mux_mult_ctrl <= '0';
next_state <= NOP;
end if;
-- State for the calculations of the Montgomery iterations
when CALCULATE_START =>
mux_mult_ctrl <= '1';
ready <= '0';
-- End of iterations (counter contains the 'word_size' number)
if (position_counter = (word_size - 1)) then
out_reg_en <= '0';
next_state <= STOP;
-- Calculation process
else
out_reg_en <= '1';
next_state <= CALCULATE_START;
end if;
-- End of the calculations
when STOP =>
ready <= '1';
mux_mult_ctrl <= '1';
out_reg_en <= '0';
if (start = '1') then
next_state <= STOP;
else
next_state <= NOP;
end if;
end case;
end process SM;
 
-- Shift register enabling proper calculations of the all Montgomery iterations
shift : process (clk, state)
begin
if (clk = '0' and clk'Event) then
if (state = CALCULATE_START) then
shift_reg <= shift_reg(0) & shift_reg(word_size - 1 downto 1);
else
shift_reg <= x;
end if;
end if;
end process shift;
 
-- Process for the state change between each clock tick
state_control : process (clk, start)
begin
if (start = '0') then
state <= NOP;
elsif (clk = '1' and clk'Event) then
state <= next_state;
end if;
end process state_control;
 
-- Counter for controlling the number of the montgomery iterations during counting
couner_modifier : process (clk)
begin
if (clk = '1' and clk'Event) then
if (state = CALCULATE_START) then
position_counter <= position_counter + 1;
else
position_counter <= (others => '0');
end if;
end if;
end process couner_modifier;
end Behavioral;
/trunk/rtl/vhdl/mod_mult/ModularMultiplierIterative.vhd
0,0 → 1,195
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- Montgomery modular multiplier main module. It combines all ----
---- subomponents. It takes two numbers and modulus as the input ----
---- and returns the Montgomery product A*B*(R^{-1}) mod M ----
---- where R^{-1} is the modular multiplicative inverse. ----
---- R*R^{-1} == 1 mod M ----
---- R = 2^word_length mod M ----
---- and word_length is the binary width of the ----
---- operated word (in this case 64 bit) ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.STD_LOGIC_UNSIGNED.ALL;
use IEEE.NUMERIC_STD.ALL;
use work.properties.ALL;
 
-- Uncomment the following library declaration if using
-- arithmetic functions with Signed or Unsigned values
--use IEEE.NUMERIC_STD.ALL;
 
-- Uncomment the following library declaration if instantiating
-- any Xilinx primitives in this code.
--library UNISIM;
--use UNISIM.VComponents.all;
 
entity ModularMultiplierIterative is
generic (
word_size : integer := WORD_LENGTH
);
port (
A : in STD_LOGIC_VECTOR(word_size - 1 downto 0); -- multiplicand
B : in STD_LOGIC_VECTOR(word_size - 1 downto 0); -- multiplier
M : in STD_LOGIC_VECTOR(word_size - 1 downto 0); -- modulus
start : in STD_LOGIC;
product : out STD_LOGIC_VECTOR(word_size - 1 downto 0); -- product
ready : out STD_LOGIC;
clk : in STD_LOGIC
);
end ModularMultiplierIterative;
 
architecture Behavioral of ModularMultiplierIterative is
 
-- Multiplexer
component MontMult4inMux is
generic (
word_size : integer := WORD_LENGTH
);
port (
ctrl : in STD_LOGIC_VECTOR(1 downto 0);
zero : in STD_LOGIC_VECTOR(word_size downto 0);
M : in STD_LOGIC_VECTOR(word_size downto 0);
Y : in STD_LOGIC_VECTOR(word_size downto 0);
YplusM : in STD_LOGIC_VECTOR(word_size downto 0);
output : out STD_LOGIC_VECTOR(word_size downto 0)
);
end component MontMult4inMux;
 
-- State machine
component ModMultIter_SM is
generic (
word_size : integer := WORD_LENGTH
);
port(
x : in STD_LOGIC_VECTOR(word_size - 1 downto 0);
start : in STD_LOGIC;
clk : in STD_LOGIC;
s_0 : in STD_LOGIC;
y_0 : in STD_LOGIC;
ready : out STD_LOGIC;
out_reg_en : out STD_LOGIC;
mux_mult_ctrl : out STD_LOGIC;
mux_4in_ctrl : out STD_LOGIC_VECTOR(1 downto 0)
);
end component ModMultIter_SM;
 
-- Signals
signal Mi : STD_LOGIC_VECTOR(word_size downto 0);
signal Yi : STD_LOGIC_VECTOR(word_size downto 0);
signal sumYM : STD_LOGIC_VECTOR(word_size downto 0);
signal zero_sig : STD_LOGIC_VECTOR(word_size downto 0) := (others => '0');
signal four_in_mux_out : STD_LOGIC_VECTOR(word_size downto 0);
 
signal mux_4in_ctrl_sig : STD_LOGIC_VECTOR(1 downto 0);
signal mult_mux_ctrl_sig : STD_LOGIC;
 
signal mult_mux_out : STD_LOGIC_VECTOR(word_size downto 0);
signal out_reg_sig : STD_LOGIC_VECTOR(word_size downto 0);
signal product_sig : STD_LOGIC_VECTOR(word_size downto 0);
signal out_en : STD_LOGIC;
 
signal sum_mult_out : STD_LOGIC_VECTOR(word_size + 1 downto 0);
signal sum_div_2 : STD_LOGIC_VECTOR(word_size downto 0);
 
begin
zero_sig <= (others => '0'); -- '0'
-- 'widening' to store the intermediate steps
Mi <= '0' & M;
Yi <= '0' & B;
-- Operations needed to compute the Montgomery multiplications
sum_div_2 <= sum_mult_out(word_size + 1 downto 1);
sum_mult_out <= ('0' & four_in_mux_out) + ('0' & mult_mux_out);
sumYM <= ('0' & B) + ('0' & M);
 
-- Multiplexer component
four_in_mux : MontMult4inMux port map(
ctrl => mux_4in_ctrl_sig, zero => zero_sig, M => Mi, Y => Yi,
YplusM => sumYM, output => four_in_mux_out
);
 
-- Two input asynchronuos multiplexer for output 'not clear' code due to
-- 'historical works'
mult_mux_out <= (others => '0') when (mult_mux_ctrl_sig = '0') else
out_reg_sig;
 
-- State machine
state_machine : ModMultIter_SM port map(
x => A,
start => start,
clk => clk,
s_0 => out_reg_sig(0),
y_0 => B(0),
ready => ready,
out_reg_en => out_en,
mux_mult_ctrl => mult_mux_ctrl_sig,
mux_4in_ctrl => mux_4in_ctrl_sig
);
-- Register like structure for signal synchronous work
clock : process(clk, start)
begin
if (clk = '1' and clk'Event) then
if (start = '0') then
out_reg_sig <= (others => '0');
elsif out_en = '1' then
out_reg_sig <= sum_div_2;
end if;
end if;
end process clock;
-- One additional 'subtract' component which was added after
-- first experiments with Montgomery multiplication. It was
-- observed that sometimes intermediate step can be higher
-- than modulus. In this situation 'M' substraction is
-- compulsory
product_proc : process(clk, Mi, out_reg_sig)
begin
if(out_reg_sig < ("0" & Mi)) then
product_sig <= out_reg_sig;
else
product_sig <= out_reg_sig - Mi;
end if;
end process product_proc;
product <= product_sig(word_size - 1 downto 0);
 
end Behavioral;
/trunk/rtl/vhdl/commons/properties_32bit.vhd
0,0 → 1,113
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- Properties file for multiplier and exponentiator ----
---- (32 bit). ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
 
library IEEE;
use IEEE.STD_LOGIC_1164.all;
 
package properties is
 
-- Declare constants
constant BYTE : INTEGER := 8;
constant WORD_LENGTH : INTEGER := 32;
constant WORD_INTEGER : INTEGER := 6;
constant WORD_INT_LOG : INTEGER := 3;
constant WORD_INT_LOG_STR : STD_LOGIC_VECTOR(WORD_INT_LOG - 1 downto 0) := "110";
 
constant count_up : STD_LOGIC_VECTOR(1 downto 0) := "00";
constant count_down : STD_LOGIC_VECTOR(1 downto 0) := "01";
constant do_nothing : STD_LOGIC_VECTOR(1 downto 0) := "11";
 
type multiplier_states is (NOP, CALCULATE_START, STOP);
 
type finalizer_states is (FIRST_RUN, NOP,
READ_DATA_HASH_M, READ_DATA_C1, READ_DATA_N, READ_DATA_E, READ_DATA_D2, READ_DATA_CINV,
COUNT_C2, EXP_Z_C2, SAVE_EXP_Z_C2, EXP_P_C2, SAVE_EXP_P_C2, EXP_CONTROL_C2, EXP_END_C2, SAVE_EXP_MULT_C2,
COUNT_Cinv, MULT_CINV, SAVE_MULT_CINV,
COUNT_C, MULT_C, SAVE_MULT_C,
COUNT_M, EXP_Z_M, SAVE_EXP_Z_M, EXP_P_M, SAVE_EXP_P_M, EXP_CONTROL_M, EXP_END_M, SAVE_EXP_M,
MAKE_COMPARE, COMP, COMPARE_RESULT,
INFO_RESULT, SHOW_RESULT, FAIL_STATE);
 
type fin_data_ctrl_states is (NOP, PAD_FAIL, PAD_FAIL_NOP, PAD_FAIL_DECODE,
DECODE_IN, READ_DATA, DECODE_READ, DECODE_READ_PROP, MAKE_FINALIZE, OUTPUT_DATA, INFO_STATE,
TEMPORARY_STATE, DATA_TO_OUT_PROPAGATE, DATA_TO_OUT_PROPAGATE2, MOVE_DATA, MOVE_OUTPUT_DATA);
 
---- mnemonics for finalizer
constant mn_read_hash_m : STD_LOGIC_VECTOR(7 downto 0) := "00000001";
constant mn_read_c1 : STD_LOGIC_VECTOR(7 downto 0) := "00000010";
constant mn_read_n : STD_LOGIC_VECTOR(7 downto 0) := "00000011";
constant mn_read_e : STD_LOGIC_VECTOR(7 downto 0) := "00000100";
constant mn_read_d2 : STD_LOGIC_VECTOR(7 downto 0) := "00000110";
constant mn_read_cinv : STD_LOGIC_VECTOR(7 downto 0) := "00000111";
constant mn_finalize : STD_LOGIC_VECTOR(7 downto 0) := "00001000";
constant mn_show_result : STD_LOGIC_VECTOR(7 downto 0) := "00001001";
constant mn_show_status : STD_LOGIC_VECTOR(7 downto 0) := "00001010";
constant mn_prepare_for_data : STD_LOGIC_VECTOR(7 downto 0) := "00001011";
 
---- addresses for memory data
constant addr_hashM : STD_LOGIC_VECTOR(3 downto 0) := "0000";
constant addr_c1 : STD_LOGIC_VECTOR(3 downto 0) := "0001";
constant addr_N : STD_LOGIC_VECTOR(3 downto 0) := "0010";
constant addr_E : STD_LOGIC_VECTOR(3 downto 0) := "0011";
constant addr_d2 : STD_LOGIC_VECTOR(3 downto 0) := "0100";
constant addr_c2 : STD_LOGIC_VECTOR(3 downto 0) := "0101";
constant addr_c : STD_LOGIC_VECTOR(3 downto 0) := "0110";
constant addr_hashMc : STD_LOGIC_VECTOR(3 downto 0) := "0111";
constant addr_cinv : STD_LOGIC_VECTOR(3 downto 0) := "1000";
constant addr_one : STD_LOGIC_VECTOR(3 downto 0) := "1001";
constant addr_unused : STD_LOGIC_VECTOR(3 downto 0) := "1101";
constant addr_z : STD_LOGIC_VECTOR(3 downto 0) := "1110";
constant addr_p : STD_LOGIC_VECTOR(3 downto 0) := "1111";
 
---- help_statuses_for_clarity
constant stat_all_data_readed : STD_LOGIC_VECTOR(5 downto 0) := "111111";
constant stat_clear_status : STD_LOGIC_VECTOR(5 downto 0) := "000000";
 
end properties;
 
package body properties is
end properties;
/trunk/rtl/vhdl/commons/properties_64bit.vhd
0,0 → 1,113
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- Properties file for multiplier and exponentiator ----
---- (64 bit). ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
 
library IEEE;
use IEEE.STD_LOGIC_1164.all;
 
package properties is
 
-- Declare constants
constant BYTE : INTEGER := 8;
constant WORD_LENGTH : INTEGER := 64;
constant WORD_INTEGER : INTEGER := 7;
constant WORD_INT_LOG : INTEGER := 3;
constant WORD_INT_LOG_STR : STD_LOGIC_VECTOR(WORD_INT_LOG - 1 downto 0) := "111";
 
constant count_up : STD_LOGIC_VECTOR(1 downto 0) := "00";
constant count_down : STD_LOGIC_VECTOR(1 downto 0) := "01";
constant do_nothing : STD_LOGIC_VECTOR(1 downto 0) := "11";
 
type multiplier_states is (NOP, CALCULATE_START, STOP);
 
type finalizer_states is (FIRST_RUN, NOP,
READ_DATA_HASH_M, READ_DATA_C1, READ_DATA_N, READ_DATA_E, READ_DATA_D2, READ_DATA_CINV,
COUNT_C2, EXP_Z_C2, SAVE_EXP_Z_C2, EXP_P_C2, SAVE_EXP_P_C2, EXP_CONTROL_C2, EXP_END_C2, SAVE_EXP_MULT_C2,
COUNT_Cinv, MULT_CINV, SAVE_MULT_CINV,
COUNT_C, MULT_C, SAVE_MULT_C,
COUNT_M, EXP_Z_M, SAVE_EXP_Z_M, EXP_P_M, SAVE_EXP_P_M, EXP_CONTROL_M, EXP_END_M, SAVE_EXP_M,
MAKE_COMPARE, COMP, COMPARE_RESULT,
INFO_RESULT, SHOW_RESULT, FAIL_STATE);
 
type fin_data_ctrl_states is (NOP, PAD_FAIL, PAD_FAIL_NOP, PAD_FAIL_DECODE,
DECODE_IN, READ_DATA, DECODE_READ, DECODE_READ_PROP, MAKE_FINALIZE, OUTPUT_DATA, INFO_STATE,
TEMPORARY_STATE, DATA_TO_OUT_PROPAGATE, DATA_TO_OUT_PROPAGATE2, MOVE_DATA, MOVE_OUTPUT_DATA);
 
---- mnemonics for finalizer
constant mn_read_hash_m : STD_LOGIC_VECTOR(7 downto 0) := "00000001";
constant mn_read_c1 : STD_LOGIC_VECTOR(7 downto 0) := "00000010";
constant mn_read_n : STD_LOGIC_VECTOR(7 downto 0) := "00000011";
constant mn_read_e : STD_LOGIC_VECTOR(7 downto 0) := "00000100";
constant mn_read_d2 : STD_LOGIC_VECTOR(7 downto 0) := "00000110";
constant mn_read_cinv : STD_LOGIC_VECTOR(7 downto 0) := "00000111";
constant mn_finalize : STD_LOGIC_VECTOR(7 downto 0) := "00001000";
constant mn_show_result : STD_LOGIC_VECTOR(7 downto 0) := "00001001";
constant mn_show_status : STD_LOGIC_VECTOR(7 downto 0) := "00001010";
constant mn_prepare_for_data : STD_LOGIC_VECTOR(7 downto 0) := "00001011";
 
---- addresses for memory data
constant addr_hashM : STD_LOGIC_VECTOR(3 downto 0) := "0000";
constant addr_c1 : STD_LOGIC_VECTOR(3 downto 0) := "0001";
constant addr_N : STD_LOGIC_VECTOR(3 downto 0) := "0010";
constant addr_E : STD_LOGIC_VECTOR(3 downto 0) := "0011";
constant addr_d2 : STD_LOGIC_VECTOR(3 downto 0) := "0100";
constant addr_c2 : STD_LOGIC_VECTOR(3 downto 0) := "0101";
constant addr_c : STD_LOGIC_VECTOR(3 downto 0) := "0110";
constant addr_hashMc : STD_LOGIC_VECTOR(3 downto 0) := "0111";
constant addr_cinv : STD_LOGIC_VECTOR(3 downto 0) := "1000";
constant addr_one : STD_LOGIC_VECTOR(3 downto 0) := "1001";
constant addr_unused : STD_LOGIC_VECTOR(3 downto 0) := "1101";
constant addr_z : STD_LOGIC_VECTOR(3 downto 0) := "1110";
constant addr_p : STD_LOGIC_VECTOR(3 downto 0) := "1111";
 
---- help_statuses_for_clarity
constant stat_all_data_readed : STD_LOGIC_VECTOR(5 downto 0) := "111111";
constant stat_clear_status : STD_LOGIC_VECTOR(5 downto 0) := "000000";
 
end properties;
 
package body properties is
end properties;
/trunk/rtl/vhdl/commons/MontMult4inMux.vhd
0,0 → 1,77
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- Simple construction of 4 input asynchronous multiplexer. ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use work.properties.ALL;
 
-- Uncomment the following library declaration if using
-- arithmetic functions with Signed or Unsigned values
--use IEEE.NUMERIC_STD.ALL;
 
-- Uncomment the following library declaration if instantiating
-- any Xilinx primitives in this code.
--library UNISIM;
--use UNISIM.VComponents.all;
 
entity MontMult4inMux is
generic (
word_size : integer := WORD_LENGTH
);
port (
ctrl : in STD_LOGIC_VECTOR(1 downto 0);
zero : in STD_LOGIC_VECTOR(word_size downto 0);
M : in STD_LOGIC_VECTOR(word_size downto 0);
Y : in STD_LOGIC_VECTOR(word_size downto 0);
YplusM : in STD_LOGIC_VECTOR(word_size downto 0);
output : out STD_LOGIC_VECTOR(word_size downto 0)
);
end MontMult4inMux;
 
architecture Behavioral of MontMult4inMux is
 
begin
output <= zero when ctrl = "00" else
M when ctrl = "01" else
Y when ctrl = "10" else
YplusM;
end Behavioral;
/trunk/rtl/vhdl/commons/properties.vhd
0,0 → 1,112
-----------------------------------------------------------------------
---- ----
---- Montgomery modular multiplier and exponentiator ----
---- ----
---- This file is part of the Montgomery modular multiplier ----
---- and exponentiator project ----
---- http://opencores.org/project,mod_mult_exp ----
---- ----
---- Description: ----
---- Properties file for multiplier and exponentiator ----
---- (512 bit). ----
---- To Do: ----
---- ----
---- Author(s): ----
---- - Krzysztof Gajewski, gajos@opencores.org ----
---- k.gajewski@gmail.com ----
---- ----
-----------------------------------------------------------------------
---- ----
---- Copyright (C) 2014 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.opencores.org/lgpl.shtml ----
---- ----
-----------------------------------------------------------------------
library IEEE;
use IEEE.STD_LOGIC_1164.all;
 
package properties is
 
-- Declare constants
constant BYTE : INTEGER := 8;
 
constant WORD_LENGTH : INTEGER := 512;
constant WORD_INTEGER : INTEGER := 10;
constant WORD_INT_LOG : INTEGER := 6;
constant WORD_INT_LOG_STR : STD_LOGIC_VECTOR(WORD_INT_LOG - 1 downto 0) := "111111";
 
constant count_up : STD_LOGIC_VECTOR(1 downto 0) := "00";
constant count_down : STD_LOGIC_VECTOR(1 downto 0) := "01";
constant do_nothing : STD_LOGIC_VECTOR(1 downto 0) := "11";
 
type multiplier_states is (NOP, CALCULATE_START, STOP);
 
type finalizer_states is (FIRST_RUN, NOP,
READ_DATA_HASH_M, READ_DATA_C1, READ_DATA_N, READ_DATA_E, READ_DATA_D2, READ_DATA_CINV,
COUNT_C2, EXP_Z_C2, SAVE_EXP_Z_C2, EXP_P_C2, SAVE_EXP_P_C2, EXP_CONTROL_C2, EXP_END_C2, SAVE_EXP_MULT_C2,
COUNT_Cinv, MULT_CINV, SAVE_MULT_CINV,
COUNT_C, MULT_C, SAVE_MULT_C,
COUNT_M, EXP_Z_M, SAVE_EXP_Z_M, EXP_P_M, SAVE_EXP_P_M, EXP_CONTROL_M, EXP_END_M, SAVE_EXP_M,
MAKE_COMPARE, COMP, COMPARE_RESULT,
INFO_RESULT, SHOW_RESULT, FAIL_STATE);
 
type fin_data_ctrl_states is (NOP, PAD_FAIL, PAD_FAIL_NOP, PAD_FAIL_DECODE,
DECODE_IN, READ_DATA, DECODE_READ, DECODE_READ_PROP, MAKE_FINALIZE, OUTPUT_DATA, INFO_STATE,
TEMPORARY_STATE, DATA_TO_OUT_PROPAGATE, DATA_TO_OUT_PROPAGATE2, MOVE_DATA, MOVE_OUTPUT_DATA);
 
---- mnemonics for finalizer
constant mn_read_hash_m : STD_LOGIC_VECTOR(7 downto 0) := "00000001";
constant mn_read_c1 : STD_LOGIC_VECTOR(7 downto 0) := "00000010";
constant mn_read_n : STD_LOGIC_VECTOR(7 downto 0) := "00000011";
constant mn_read_e : STD_LOGIC_VECTOR(7 downto 0) := "00000100";
constant mn_read_d2 : STD_LOGIC_VECTOR(7 downto 0) := "00000110";
constant mn_read_cinv : STD_LOGIC_VECTOR(7 downto 0) := "00000111";
constant mn_finalize : STD_LOGIC_VECTOR(7 downto 0) := "00001000";
constant mn_show_result : STD_LOGIC_VECTOR(7 downto 0) := "00001001";
constant mn_show_status : STD_LOGIC_VECTOR(7 downto 0) := "00001010";
constant mn_prepare_for_data : STD_LOGIC_VECTOR(7 downto 0) := "00001011";
 
---- addresses for memory data
constant addr_hashM : STD_LOGIC_VECTOR(3 downto 0) := "0000";
constant addr_c1 : STD_LOGIC_VECTOR(3 downto 0) := "0001";
constant addr_N : STD_LOGIC_VECTOR(3 downto 0) := "0010";
constant addr_E : STD_LOGIC_VECTOR(3 downto 0) := "0011";
constant addr_d2 : STD_LOGIC_VECTOR(3 downto 0) := "0100";
constant addr_c2 : STD_LOGIC_VECTOR(3 downto 0) := "0101";
constant addr_c : STD_LOGIC_VECTOR(3 downto 0) := "0110";
constant addr_hashMc : STD_LOGIC_VECTOR(3 downto 0) := "0111";
constant addr_cinv : STD_LOGIC_VECTOR(3 downto 0) := "1000";
constant addr_one : STD_LOGIC_VECTOR(3 downto 0) := "1001";
constant addr_unused : STD_LOGIC_VECTOR(3 downto 0) := "1101";
constant addr_z : STD_LOGIC_VECTOR(3 downto 0) := "1110";
constant addr_p : STD_LOGIC_VECTOR(3 downto 0) := "1111";
 
---- help_statuses_for_clarity
constant stat_all_data_readed : STD_LOGIC_VECTOR(5 downto 0) := "111111";
constant stat_clear_status : STD_LOGIC_VECTOR(5 downto 0) := "000000";
 
end properties;
 
package body properties is
end properties;
trunk/rtl/vhdl/commons Property changes : Added: bugtraq:number ## -0,0 +1 ## +true \ No newline at end of property Index: trunk/sim/rtl_sim/bin/isim.cmd =================================================================== --- trunk/sim/rtl_sim/bin/isim.cmd (nonexistent) +++ trunk/sim/rtl_sim/bin/isim.cmd (revision 3) @@ -0,0 +1,4 @@ +onerror {resume} +wave add / +run all +exit Index: trunk/sim/rtl_sim/bin/ModularMultiplierIterative32bitTB_stx_beh.prj =================================================================== --- trunk/sim/rtl_sim/bin/ModularMultiplierIterative32bitTB_stx_beh.prj (nonexistent) +++ trunk/sim/rtl_sim/bin/ModularMultiplierIterative32bitTB_stx_beh.prj (revision 3) @@ -0,0 +1,5 @@ +vhdl isim_temp "../../../rtl/vhdl/commons/properties_32bit.vhd" +vhdl isim_temp "../../../rtl/vhdl/mod_mult/ModMultIter_SM.vhd" +vhdl isim_temp "../../../rtl/vhdl/commons/MontMult4inMux.vhd" +vhdl isim_temp "../../../rtl/vhdl/mod_mult/ModularMultiplierIterative.vhd" +vhdl isim_temp "../../../bench/vhdl/mod_mult/ModularMultiplierIterative32bitTB.vhd" Index: trunk/sim/rtl_sim/bin/ModularMultiplierIterative32bitTB_beh.prj =================================================================== --- trunk/sim/rtl_sim/bin/ModularMultiplierIterative32bitTB_beh.prj (nonexistent) +++ trunk/sim/rtl_sim/bin/ModularMultiplierIterative32bitTB_beh.prj (revision 3) @@ -0,0 +1,5 @@ +vhdl work "../../../rtl/vhdl/commons/properties_32bit.vhd" +vhdl work "../../../rtl/vhdl/mod_mult/ModMultIter_SM.vhd" +vhdl work "../../../rtl/vhdl/commons/MontMult4inMux.vhd" +vhdl work "../../../rtl/vhdl/mod_mult/ModularMultiplierIterative.vhd" +vhdl work "../../../bench/vhdl/mod_mult/ModularMultiplierIterative32bitTB.vhd" Index: trunk/sim/rtl_sim/bin/ModularMultiplierIterative512bitTB_stx_beh.prj =================================================================== --- trunk/sim/rtl_sim/bin/ModularMultiplierIterative512bitTB_stx_beh.prj (nonexistent) +++ trunk/sim/rtl_sim/bin/ModularMultiplierIterative512bitTB_stx_beh.prj (revision 3) @@ -0,0 +1,5 @@ +vhdl isim_temp "../../../rtl/vhdl/commons/properties.vhd" +vhdl isim_temp "../../../rtl/vhdl/mod_mult/ModMultIter_SM.vhd" +vhdl isim_temp "../../../rtl/vhdl/commons/MontMult4inMux.vhd" +vhdl isim_temp "../../../rtl/vhdl/mod_mult/ModularMultiplierIterative.vhd" +vhdl isim_temp "../../../bench/vhdl/mod_mult/ModularMultiplierIterative512bitTB.vhd" Index: trunk/sim/rtl_sim/bin/ModularMultiplierIterative512bitTB_beh.prj =================================================================== --- trunk/sim/rtl_sim/bin/ModularMultiplierIterative512bitTB_beh.prj (nonexistent) +++ trunk/sim/rtl_sim/bin/ModularMultiplierIterative512bitTB_beh.prj (revision 3) @@ -0,0 +1,5 @@ +vhdl work "../../../rtl/vhdl/commons/properties.vhd" +vhdl work "../../../rtl/vhdl/mod_mult/ModMultIter_SM.vhd" +vhdl work "../../../rtl/vhdl/commons/MontMult4inMux.vhd" +vhdl work "../../../rtl/vhdl/mod_mult/ModularMultiplierIterative.vhd" +vhdl work "../../../bench/vhdl/mod_mult/ModularMultiplierIterative512bitTB.vhd" Index: trunk/sim/rtl_sim/bin/ModularMultiplierIterative64bitTB_stx_beh.prj =================================================================== --- trunk/sim/rtl_sim/bin/ModularMultiplierIterative64bitTB_stx_beh.prj (nonexistent) +++ trunk/sim/rtl_sim/bin/ModularMultiplierIterative64bitTB_stx_beh.prj (revision 3) @@ -0,0 +1,5 @@ +vhdl isim_temp "../../../rtl/vhdl/commons/properties_64bit.vhd" +vhdl isim_temp "../../../rtl/vhdl/mod_mult/ModMultIter_SM.vhd" +vhdl isim_temp "../../../rtl/vhdl/commons/MontMult4inMux.vhd" +vhdl isim_temp "../../../rtl/vhdl/mod_mult/ModularMultiplierIterative.vhd" +vhdl isim_temp "../../../bench/vhdl/mod_mult/ModularMultiplierIterative64bitTB.vhd" Index: trunk/sim/rtl_sim/bin/Makefile =================================================================== --- trunk/sim/rtl_sim/bin/Makefile (nonexistent) +++ trunk/sim/rtl_sim/bin/Makefile (revision 3) @@ -0,0 +1,44 @@ +PROJECT=present-pure + +RM=/bin/rm -rf + +PLATFORM=xc3s500e-fg320-5 + +XILINX_DIR="D:/Programy/Xilinx/14.2/ISE_DS/ISE/bin/nt64/" +FUSE=$(XILINX_DIR)"unwrapped/fuse.exe" +VHPCOMP=$(XILINX_DIR)"vhpcomp.exe" +PATH=${XILINX}/bin/${SYSOP}:/cygdrive/D/Programy/Xilinx/14.2/ISE_DS/ISE/sysgen/bin/nt64/:/cygdrive/D/Programy/Xilinx/14.2/ISE_DS/ISE/lib/nt64/ + +clean: + $(RM) ./isim + $(RM) ./isim.wdb + $(RM) *.log + $(RM) *.xmsgs + $(RM) ./fuseRelaunch.cmd + $(RM) *.exe + +exports: + export DISPLAY=:0 + export XILINX=D:/Programy/Xilinx/14.2/ISE_DS/ISE + export SYSOP=nt64 + export PATH=${XILINX}/bin/${SYSOP} + export LD_LIBRARY_PATH=${XILINX}/lib/${SYSOP} + +ModMult32: + $(VHPCOMP) -work isim_temp -intstyle ise -prj ./ModularMultiplierIterative32bitTB_stx_beh.prj + $(FUSE) -intstyle ise -incremental -o ModularMultiplierIterative32bitTB_isim_beh.exe -prj ./ModularMultiplierIterative32bitTB_beh.prj work.ModularMultiplierIterative32bitTB + +run_ModMult32: exports ModMult32 + "./ModularMultiplierIterative32bitTB_isim_beh.exe" -intstyle ise -tclbatch isim.cmd -wdb "./ModularMultiplierIterative32bitTB_isim_beh.wdb" + +ModMult64: + $(FUSE) -intstyle ise -incremental -o ModularMultiplierIterative64bitTB_isim_beh.exe -prj ./ModularMultiplierIterative64bitTB_beh.prj work.ModularMultiplierIterative64bitTB + +run_ModMult64: exports ModMult64 + "./ModularMultiplierIterative64bitTB_isim_beh.exe" -intstyle ise -tclbatch isim.cmd -wdb "ModularMultiplierIterative64bitTB_isim_beh.wdb" + +ModMult512: + $(FUSE) -intstyle ise -incremental -o ModularMultiplierIterative512bitTB_isim_beh.exe -prj ./ModularMultiplierIterative512bitTB_beh.prj work.ModularMultiplierIterative512bitTB + +run_ModMult512: exports ModMult512 + "./ModularMultiplierIterative512bitTB_isim_beh.exe" -intstyle ise -tclbatch isim.cmd -wdb "ModularMultiplierIterative512bitTB_isim_beh.wdb" \ No newline at end of file Index: trunk/sim/rtl_sim/bin/ModularMultiplierIterative64bitTB_beh.prj =================================================================== --- trunk/sim/rtl_sim/bin/ModularMultiplierIterative64bitTB_beh.prj (nonexistent) +++ trunk/sim/rtl_sim/bin/ModularMultiplierIterative64bitTB_beh.prj (revision 3) @@ -0,0 +1,5 @@ +vhdl work "../../../rtl/vhdl/commons/properties_64bit.vhd" +vhdl work "../../../rtl/vhdl/mod_mult/ModMultIter_SM.vhd" +vhdl work "../../../rtl/vhdl/commons/MontMult4inMux.vhd" +vhdl work "../../../rtl/vhdl/mod_mult/ModularMultiplierIterative.vhd" +vhdl work "../../../bench/vhdl/mod_mult/ModularMultiplierIterative64bitTB.vhd" Index: trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.prj =================================================================== --- trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.prj (nonexistent) +++ trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.prj (revision 3) @@ -0,0 +1,4 @@ +vhdl work "../../../rtl/vhdl/commons/properties.vhd" +vhdl work "../../../rtl/vhdl/mod_mult/ModMultIter_SM.vhd" +vhdl work "../../../rtl/vhdl/commons/MontMult4inMux.vhd" +vhdl work "../../../rtl/vhdl/mod_mult/ModularMultiplierIterative.vhd" Index: trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.xst =================================================================== --- trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.xst (nonexistent) +++ trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.xst (revision 3) @@ -0,0 +1,56 @@ +set -tmpdir "xst/projnav.tmp" +set -xsthdpdir "xst" +run +-ifn ModularMultiplierIterative.prj +-ifmt mixed +-ofn ModularMultiplierIterative +-ofmt NGC +-p xc3s500e-4-fg320 +-top ModularMultiplierIterative +-opt_mode Speed +-opt_level 1 +-iuc NO +-keep_hierarchy Soft +-netlist_hierarchy As_Optimized +-rtlview Yes +-glob_opt AllClockNets +-read_cores YES +-write_timing_constraints NO +-cross_clock_analysis NO +-hierarchy_separator / +-bus_delimiter <> +-case Maintain +-slice_utilization_ratio 100 +-bram_utilization_ratio 100 +-verilog2001 YES +-fsm_extract YES -fsm_encoding Auto +-safe_implementation No +-fsm_style LUT +-ram_extract Yes +-ram_style Auto +-rom_extract Yes +-mux_style Auto +-decoder_extract YES +-priority_extract Yes +-shreg_extract YES +-shift_extract YES +-xor_collapse YES +-rom_style Auto +-auto_bram_packing NO +-mux_extract Yes +-resource_sharing YES +-async_to_sync NO +-mult_style Auto +-iobuf YES +-max_fanout 100000 +-bufg 24 +-register_duplication YES +-register_balancing No +-slice_packing YES +-optimize_primitives NO +-use_clock_enable Yes +-use_sync_set Yes +-use_sync_reset Yes +-iob Auto +-equivalent_register_removal YES +-slice_utilization_ratio_maxmargin 5 Index: trunk/syn/XC3ES500/mod_mult/Makefile =================================================================== --- trunk/syn/XC3ES500/mod_mult/Makefile (nonexistent) +++ trunk/syn/XC3ES500/mod_mult/Makefile (revision 3) @@ -0,0 +1,56 @@ +PROJECT=mont-mult + +RM=/bin/rm -rf + +PLATFORM=xc3s500e-fg320-5 + +XILINX_DIR="D:/Programy/Xilinx/14.2/ISE_DS/ISE/bin/nt64/" +XST_DIR=$(XILINX_DIR)"xst.exe" +NGDBUILD_DIR=$(XILINX_DIR)"ngdbuild.exe" +MAP=$(XILINX_DIR)"map.exe" +PAR=$(XILINX_DIR)"par.exe" +TRCE=$(XILINX_DIR)"trce.exe" +BITGEN=$(XILINX_DIR)"bitgen.exe" + +clean: clean_postgen + $(RM) "./out/"*.* + $(RM) "./log/"*.* + $(RM) "./out/" + $(RM) "./log/" + +clean_postgen: + $(RM) "./_xmsgs" + $(RM) "./_ngo" + $(RM) "./xlnx_auto_0_xdb" + $(RM) "./xst" + $(RM) *_vhdl.prj *.bgn *.bld *.csv *.drc *.lso *.map *.mrp *.ncd *.ngc *.ngd *.ngm *.ngr *.pad *.par *.pcf *.ptwx *.syr *.twr *.twx *.unroutes *.xpi *.xwbt + +synthesize: clean + mkdir "./xst" + mkdir "./xst/projnav.tmp" + mkdir "./out/" + mkdir "./log/" + $(XST_DIR) -intstyle ise -ifn "./ModularMultiplierIterative.xst" -ofn "./ModularMultiplierIterative.syr" + +translate: synthesize + $(NGDBUILD_DIR) -intstyle ise -dd _ngo -nt timestamp -i -p $(PLATFORM) "ModularMultiplierIterative.ngc" ModularMultiplierIterative.ngd + +map: translate + $(MAP) -intstyle ise -p $(PLATFORM) -cm area -ir off -pr off -c 100 -o ModularMultiplierIterative_map.ncd ModularMultiplierIterative.ngd ModularMultiplierIterative.pcf + +par: map + $(PAR) -w -intstyle ise -ol high -t 1 ModularMultiplierIterative_map.ncd ModularMultiplierIterative.ncd ModularMultiplierIterative.pcf + +trce: par + $(TRCE) -intstyle ise -v 3 -s 4 -n 3 -fastpaths -xml ModularMultiplierIterative.twx ModularMultiplierIterative.ncd -o ModularMultiplierIterative.twr ModularMultiplierIterative.pcf + +bitgen: trce + $(BITGEN) -intstyle ise -f ModularMultiplierIterative.ut ModularMultiplierIterative.ncd + +postgen: + mv *.log ./log + mv *.xrpt ./log + mv *.txt ./log + mv *.xml ./log + mv *.html ./log + mv *.bit ./out \ No newline at end of file Index: trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.ut =================================================================== --- trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.ut (nonexistent) +++ trunk/syn/XC3ES500/mod_mult/ModularMultiplierIterative.ut (revision 3) @@ -0,0 +1,22 @@ +-w +-g DebugBitstream:No +-g Binary:no +-g CRC:Enable +-g ConfigRate:1 +-g ProgPin:PullUp +-g DonePin:PullUp +-g TckPin:PullUp +-g TdiPin:PullUp +-g TdoPin:PullUp +-g TmsPin:PullUp +-g UnusedPin:PullDown +-g UserID:0xFFFFFFFF +-g DCMShutdown:Disable +-g StartUpClk:CClk +-g DONE_cycle:4 +-g GTS_cycle:5 +-g GWE_cycle:6 +-g LCK_cycle:NoWait +-g Security:None +-g DonePipe:No +-g DriveDone:No Index: trunk/syn/XC3ES500/mod_mult =================================================================== --- trunk/syn/XC3ES500/mod_mult (nonexistent) +++ trunk/syn/XC3ES500/mod_mult (revision 3)
trunk/syn/XC3ES500/mod_mult Property changes : Added: bugtraq:number ## -0,0 +1 ## +true \ No newline at end of property

powered by: WebSVN 2.1.0

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