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

Subversion Repositories nfhc

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /nfhc/trunk
    from Rev 1 to Rev 2
    Reverse comparison

Rev 1 → Rev 2

/LICENSE.txt
0,0 → 1,37
Nugroho Free Hash Cores (NFHC) License:
------------------------------------------------------------------------
Copyright (C) 2010 Arif Endro Nugroho
All rights reserved.
 
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions
are met:
 
1. Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
2. Redistributions in binary form must reproduce the above copyright
notice, this list of conditions and the following disclaimer in the
documentation and/or other materials provided with the distribution.
 
THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
POSSIBILITY OF SUCH DAMAGE.
 
End Of License.
------------------------------------------------------------------------
 
Author Contact:
 
Arif E. Nugroho
Segaran I/27A 50184, Semarang, Central Java, Indonesia
 
mobile: +62 818 220 540
e-mail: arif_endro@yahoo.com
/sha512/sha512.vhdl
0,0 → 1,383
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
--
-- MaxMessage <= 2^64 bits
-- BlockSize == 1024 bits
-- WordSize == 64 bits
-- MDigestSize == 512 bits
-- Security == 256 bits
--
-- SHLnx = (x<<n)
-- SHRnx = (x>>n)
-- ROTRnx = (x>>n) or (x<<w-n)
-- ROTLnx = (x<<n) or (x>>w-n)
--
-- f0 = ((x and y) xor (not(x) and z)) -- Ch(x,y,z)
-- f1 = ((x and y) xor (x and z) xor (y and z) -- Maj(x,y,z)
-- f2 = ROTR 28(x) xor ROTR 34(x) xor ROTR 39(x) -- Sigma0(x)
-- f3 = ROTR 14(x) xor ROTR 18(x) xor ROTR 41(x) -- Sigma1(x)
-- f4 = ROTR 1(x) xor ROTR 8(x) xor SHR 7(x) -- Tetha0(x)
-- f5 = ROTR 19(x) xor ROTR 61(x) xor SHR 6(x) -- Tetha1(x)
--
-- h0 = 0x6a09e667f3bcc908
-- h1 = 0xbb67ae8584caa73b
-- h2 = 0x3c6ef372fe94f82b
-- h3 = 0xa54ff53a5f1d36f1
-- h4 = 0x510e527fade682d1
-- h5 = 0x9b05688c2b3e6c1f
-- h6 = 0x1f83d9abfb41bd6b
-- h7 = 0x5be0cd19137e2179
--
-- k[0-63] looks like better implemented in ROM file
-- with 64 bit in each contants it would take
-- 64 x 64 bit storage which equal to
-- 4096 bit ROM
--
-- Step 1
-- W(t) = M(t) 0 <= t <= 15 -- we need 16x32 (512) bit registers
-- W(t) = f5(W(t-2)) + W(t-7) + f4(W(t-15)) + W(t-16); 16 <= t <= 79
-- W = f5(W( 1)) + W( 6) + f4(W( 14)) + W( 15); 16 <= t <= 79
--
-- Step 2
-- a = h0; b = h1; c = h2; d = h3; e = h4; f = h5; g = h6; h = h7;
--
-- Step 3
-- for t 0 step 1 to 79 do
-- T1= h + f3(e) + f0(e, f, g) + k(t) + W(t)
-- T2= f2(a) + f1(a, b, c)
-- h = g
-- g = f
-- f = e
-- e = d + T1
-- d = c
-- c = b
-- b = a
-- a = T1 + T2
--
-- Step 4
-- H0 = a + h0;
-- H1 = b + h1;
-- H2 = c + h2;
-- H3 = d + h3;
-- H4 = e + H4;
-- H5 = f + H5;
-- H6 = g + H6;
-- H7 = h + H7;
--
-- 0 64 128 192 256 320 384 448 512 576 640 704 768 832 896 960 1024
-- 0 1 2 3 4 5 6 7 8 9 a b c d e f
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
 
entity sha512 is
port(
m : in bit_vector ( 63 downto 0); -- 32 bit data path require 16 clock to load all 512 bits of each block
init : in bit; -- initial message
ld : in bit; -- load signal
md : out bit_vector ( 63 downto 0); -- 5 clock after active valid signal is the message hash result
--probe
--a_prb : out bit_vector ( 63 downto 0);
--b_prb : out bit_vector ( 63 downto 0);
--c_prb : out bit_vector ( 63 downto 0);
--d_prb : out bit_vector ( 63 downto 0);
--e_prb : out bit_vector ( 63 downto 0);
--f_prb : out bit_vector ( 63 downto 0);
--g_prb : out bit_vector ( 63 downto 0);
--h_prb : out bit_vector ( 63 downto 0);
--k_prb : out bit_vector ( 63 downto 0);
--w_prb : out bit_vector ( 63 downto 0);
--ctr2p : out bit_vector ( 3 downto 0);
--ctr3p : out bit_vector ( 7 downto 0);
--probe
v : out bit; -- hash output valid signal one clock advance
clk : in bit; -- master clock signal
rst : in bit -- master reset signal
);
end sha512;
 
architecture phy of sha512 is
 
component c4b
port (
cnt : out bit_vector ( 3 downto 0);
clk : in bit;
rst : in bit
);
end component;
 
component c8b
port (
cnt : out bit_vector ( 7 downto 0);
clk : in bit;
rst : in bit
);
end component;
 
component romk
port (
addr : in bit_vector ( 6 downto 0);
k : out bit_vector ( 63 downto 0)
);
end component;
 
signal ih : bit_vector ( 63 downto 0);
signal h0 : bit_vector ( 63 downto 0);
signal h1 : bit_vector ( 63 downto 0);
signal h2 : bit_vector ( 63 downto 0);
signal h3 : bit_vector ( 63 downto 0);
signal h4 : bit_vector ( 63 downto 0);
signal h5 : bit_vector ( 63 downto 0);
signal h6 : bit_vector ( 63 downto 0);
signal h7 : bit_vector ( 63 downto 0);
 
signal k : bit_vector ( 63 downto 0);
 
signal im : bit_vector ( 63 downto 0);
signal iw : bit_vector ( 63 downto 0);
signal w : bit_vector ( 63 downto 0); -- current working register
signal w0 : bit_vector(1023 downto 0); -- working register 1
 
signal a : bit_vector ( 63 downto 0); -- a register
signal b : bit_vector ( 63 downto 0); -- b register
signal c : bit_vector ( 63 downto 0); -- c register
signal d : bit_vector ( 63 downto 0); -- d register
signal e : bit_vector ( 63 downto 0); -- e register
signal f : bit_vector ( 63 downto 0); -- f register
signal g : bit_vector ( 63 downto 0); -- g register
signal h : bit_vector ( 63 downto 0); -- h register
 
signal f0 : bit_vector ( 63 downto 0);
signal f1 : bit_vector ( 63 downto 0);
signal f2 : bit_vector ( 63 downto 0);
signal f3 : bit_vector ( 63 downto 0);
signal f4 : bit_vector ( 63 downto 0);
signal f5 : bit_vector ( 63 downto 0);
 
signal ctr2 : bit_vector ( 3 downto 0); -- 4 bit counter (zero to 16)
signal ctr2_rst: bit;
signal ctr3 : bit_vector ( 7 downto 0); -- 8 bit counter (zero to 255)
signal ctr3_rst: bit;
 
signal vld : bit;
signal nld : bit;
signal ild : bit;
signal ild_rst : bit;
 
begin
 
ct2 : c4b
port map (
cnt => ctr2,
clk => clk,
rst => ctr2_rst
);
ct3 : c8b
port map (
cnt => ctr3,
clk => clk,
rst => ctr3_rst
);
rom0 : romk
port map (
addr => ctr3( 6 downto 0),
k => k
);
 
--probe signal
--a_prb <= a;
--b_prb <= b;
--c_prb <= c;
--d_prb <= d;
--e_prb <= e;
--f_prb <= e;
--g_prb <= e;
--h_prb <= e;
--k_prb <= k;
--w_prb <= w;
--ctr2p <= ctr2;
--ctr3p <= ctr3;
--probe signal
 
--persistent connection
 
--f0 == ((x and y) xor (not(x) and z)) -- f0(e, f, g)
f0 <= ((e and f) xor (not(e) and g));
--f1 == ((x and y) xor (x and z) xor (y and z) -- f1(a, b, c)
f1 <= ((a and b) xor (a and c) xor (b and c));
--f2 == ROTR 28(x) xor ROTR 34(x) xor ROTR 39(x) -- f2(a)
f2 <= (a ( 27 downto 0) & a ( 63 downto 28)) xor
(a ( 33 downto 0) & a ( 63 downto 34)) xor
(a ( 38 downto 0) & a ( 63 downto 39));
--f3 == ROTR 14(x) xor ROTR 18(x) xor ROTR 41(x) -- f3(e)
f3 <= (e ( 13 downto 0) & e ( 63 downto 14)) xor
(e ( 17 downto 0) & e ( 63 downto 18)) xor
(e ( 40 downto 0) & e ( 63 downto 41));
--f4 == ROTR 1(x) xor ROTR 8(x) xor SHR 7(x) -- w0(959 downto 896)
f4 <= (w0( 896) & w0(959 downto 897)) xor
(w0(903 downto 896) & w0(959 downto 904)) xor
(B"0000000" & w0(959 downto 903));
--f5 == ROTR 19(x) xor ROTR 61(x) xor SHR 6(x) -- w0(127 downto 64)
f5 <= (w0( 82 downto 64) & w0(127 downto 83)) xor
(w0(124 downto 64) & w0(127 downto 125)) xor
(B"000000" & w0(127 downto 70));
 
with ctr2( 2 downto 0) select
ih <= h0 when B"000",
h1 when B"001",
h2 when B"010",
h3 when B"011",
h4 when B"100",
h5 when B"101",
h6 when B"110",
h7 when B"111";
 
--W == f5(W( 1)) + W( 6) + f4(W( 14)) + W( 15); 16 <= t <= 79
--iw <= f5 + w0(447 downto 384) + f4 + w0(1023 downto 960); -- FIXME this adder is very costly and NOT A PORTABLE CODE
iw <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(f5)) + unsigned(to_stdlogicvector(w0(447 downto 384))) + unsigned(to_stdlogicvector(f4)) + unsigned(to_stdlogicvector(w0(1023 downto 960))) ));
 
process (clk)
begin
if ((clk = '1') and clk'event) then
-- if (rst = '1') then -- not to reset scratch register
-- w <= (others => '0') ;
-- w0 <= (others => '0') ;
if (nld = '1') then -- 0 <= t <= 15 first 512 bit block
w <= im ;
w0(1023 downto 0)<= (w0(959 downto 0) & im);
else
w <= iw ;
w0(1023 downto 0)<= (w0(959 downto 0) & iw);
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if (rst = '1') then
ild <= '0';
nld <= '0';
im <= (others => '0');
else
ild <= nld;
nld <= ld;
im <= m;
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if ((ild_rst or rst) = '1') then
vld <= '0';
elsif (ctr3 = X"4f") then
vld <= '1';
else
vld <= '0';
end if;
end if;
end process;
 
ild_rst <= (ild xor ld) and ld;
--ctr2_rst <= ild_rst or rst or vld or (ctr2 = X"7"); -- set to count to 7 ( 8 clock)
ctr2_rst <= ild_rst or rst or vld or not(ctr2(3) or not(ctr2(2)) or not(ctr2(1)) or not(ctr2(0)));
--ctr3_rst <= ild_rst or rst or (ctr3 = X"4f"); -- set to count to 79 ( 80 clock) 0100 1111
ctr3_rst <= ild_rst or rst or not(ctr3(7) or not(ctr3(6)) or ctr3(5) or ctr3(4) or not(ctr3(3)) or not(ctr3(2)) or not(ctr3(1)) or not(ctr3(0)));
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if (init = '1') or (rst = '1') then
h0 <= X"6a09e667f3bcc908";
h1 <= X"bb67ae8584caa73b";
h2 <= X"3c6ef372fe94f82b";
h3 <= X"a54ff53a5f1d36f1";
h4 <= X"510e527fade682d1";
h5 <= X"9b05688c2b3e6c1f";
h6 <= X"1f83d9abfb41bd6b";
h7 <= X"5be0cd19137e2179";
elsif (vld = '1') then -- FIXME this adder is very costly and NOT A PORTABLE CODE
h0 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(a)) + unsigned(to_stdlogicvector(h0)) ));
h1 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(b)) + unsigned(to_stdlogicvector(h1)) ));
h2 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(c)) + unsigned(to_stdlogicvector(h2)) ));
h3 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(d)) + unsigned(to_stdlogicvector(h3)) ));
h4 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(e)) + unsigned(to_stdlogicvector(h4)) ));
h5 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(f)) + unsigned(to_stdlogicvector(h5)) ));
h6 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(g)) + unsigned(to_stdlogicvector(h6)) ));
h7 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(h)) + unsigned(to_stdlogicvector(h7)) ));
-- h0 <= a + h0;
-- h1 <= b + h1;
-- h2 <= c + h2;
-- h3 <= d + h3;
-- h4 <= e + h4;
-- h5 <= f + h5;
-- h6 <= g + h6;
-- h7 <= h + h7;
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if ((ild_rst or rst) = '1') then
a <= h0;
b <= h1;
c <= h2;
d <= h3;
e <= h4;
f <= h5;
g <= h6;
h <= h7;
else -- FIXME this adder is very costly and NOT A PORTABLE CODE
-- T1 == h + f3(e) + f0(e, f, g) + k(t) + W(t)
-- T2 == f2(a) + f1(a, b, c)
h <= g;
g <= f;
f <= e;
-- e <= d + T1 ;
-- e <= d + h + f3 + f0 + k + w;
e <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(d)) + unsigned(to_stdlogicvector(h)) + unsigned(to_stdlogicvector(f3)) + unsigned(to_stdlogicvector(f0)) + unsigned(to_stdlogicvector(k)) + unsigned(to_stdlogicvector(w)) ));
d <= c;
c <= b;
b <= a;
-- a <= T1 + T2 ;
-- a <= h + f3 + f0 + k + w + f2 + f1;
a <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(h)) + unsigned(to_stdlogicvector(f3)) + unsigned(to_stdlogicvector(f0)) + unsigned(to_stdlogicvector(k)) + unsigned(to_stdlogicvector(w)) + unsigned(to_stdlogicvector(f2)) + unsigned(to_stdlogicvector(f1)) ));
end if;
end if;
end process;
 
md <= ih;
v <= vld;
 
end phy;
/sha512/c4b.vhdl
0,0 → 1,55
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
entity c4b is
port (
cnt : out bit_vector ( 3 downto 0);
clk : in bit;
rst : in bit
);
end c4b;
 
architecture phy of c4b is
signal sum : bit_vector ( 3 downto 0); -- sum
signal cr : bit_vector ( 3 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(3 downto 1) <= ( ((sum(2 downto 0) and B"001") or (sum(2 downto 0) and cr(2 downto 0))) or (B"001" and cr(2 downto 0)) );
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= B"0000";
else
sum <= ((sum xor B"0001") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha512/romk.vhdl
0,0 → 1,132
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
entity romk is
port (
addr : in bit_vector ( 6 downto 0);
k : out bit_vector ( 63 downto 0)
);
end romk;
 
architecture phy of romk is
begin
with addr ( 6 downto 0) select
k <= X"428a2f98d728ae22" when B"0000000",
X"7137449123ef65cd" when B"0000001",
X"b5c0fbcfec4d3b2f" when B"0000010",
X"e9b5dba58189dbbc" when B"0000011",
X"3956c25bf348b538" when B"0000100",
X"59f111f1b605d019" when B"0000101",
X"923f82a4af194f9b" when B"0000110",
X"ab1c5ed5da6d8118" when B"0000111",
 
X"d807aa98a3030242" when B"0001000",
X"12835b0145706fbe" when B"0001001",
X"243185be4ee4b28c" when B"0001010",
X"550c7dc3d5ffb4e2" when B"0001011",
X"72be5d74f27b896f" when B"0001100",
X"80deb1fe3b1696b1" when B"0001101",
X"9bdc06a725c71235" when B"0001110",
X"c19bf174cf692694" when B"0001111",
 
X"e49b69c19ef14ad2" when B"0010000",
X"efbe4786384f25e3" when B"0010001",
X"0fc19dc68b8cd5b5" when B"0010010",
X"240ca1cc77ac9c65" when B"0010011",
X"2de92c6f592b0275" when B"0010100",
X"4a7484aa6ea6e483" when B"0010101",
X"5cb0a9dcbd41fbd4" when B"0010110",
X"76f988da831153b5" when B"0010111",
 
X"983e5152ee66dfab" when B"0011000",
X"a831c66d2db43210" when B"0011001",
X"b00327c898fb213f" when B"0011010",
X"bf597fc7beef0ee4" when B"0011011",
X"c6e00bf33da88fc2" when B"0011100",
X"d5a79147930aa725" when B"0011101",
X"06ca6351e003826f" when B"0011110",
X"142929670a0e6e70" when B"0011111",
 
X"27b70a8546d22ffc" when B"0100000",
X"2e1b21385c26c926" when B"0100001",
X"4d2c6dfc5ac42aed" when B"0100010",
X"53380d139d95b3df" when B"0100011",
X"650a73548baf63de" when B"0100100",
X"766a0abb3c77b2a8" when B"0100101",
X"81c2c92e47edaee6" when B"0100110",
X"92722c851482353b" when B"0100111",
 
X"a2bfe8a14cf10364" when B"0101000",
X"a81a664bbc423001" when B"0101001",
X"c24b8b70d0f89791" when B"0101010",
X"c76c51a30654be30" when B"0101011",
X"d192e819d6ef5218" when B"0101100",
X"d69906245565a910" when B"0101101",
X"f40e35855771202a" when B"0101110",
X"106aa07032bbd1b8" when B"0101111",
 
X"19a4c116b8d2d0c8" when B"0110000",
X"1e376c085141ab53" when B"0110001",
X"2748774cdf8eeb99" when B"0110010",
X"34b0bcb5e19b48a8" when B"0110011",
X"391c0cb3c5c95a63" when B"0110100",
X"4ed8aa4ae3418acb" when B"0110101",
X"5b9cca4f7763e373" when B"0110110",
X"682e6ff3d6b2b8a3" when B"0110111",
 
X"748f82ee5defb2fc" when B"0111000",
X"78a5636f43172f60" when B"0111001",
X"84c87814a1f0ab72" when B"0111010",
X"8cc702081a6439ec" when B"0111011",
X"90befffa23631e28" when B"0111100",
X"a4506cebde82bde9" when B"0111101",
X"bef9a3f7b2c67915" when B"0111110",
X"c67178f2e372532b" when B"0111111",
 
X"ca273eceea26619c" when B"1000000",
X"d186b8c721c0c207" when B"1000001",
X"eada7dd6cde0eb1e" when B"1000010",
X"f57d4f7fee6ed178" when B"1000011",
X"06f067aa72176fba" when B"1000100",
X"0a637dc5a2c898a6" when B"1000101",
X"113f9804bef90dae" when B"1000110",
X"1b710b35131c471b" when B"1000111",
 
X"28db77f523047d84" when B"1001000",
X"32caab7b40c72493" when B"1001001",
X"3c9ebe0a15c9bebc" when B"1001010",
X"431d67c49c100d4c" when B"1001011",
X"4cc5d4becb3e42b6" when B"1001100",
X"597f299cfc657e2a" when B"1001101",
X"5fcb6fab3ad6faec" when B"1001110",
X"6c44198c4a475817" when B"1001111",
 
X"0000000000000000" when others; -- maximum address is 128
 
end phy;
/sha512/sha512.c
0,0 → 1,182
#include <stdio.h>
#include "genpat.h"
 
char *inttostr(entier)
int entier;
{
char *str;
str = (char *) mbkalloc (32 * sizeof (char));
sprintf (str, "%d",entier);
return(str);
}
 
main ()
{
int i;
 
DEF_GENPAT("sha512");
SETTUNIT("ns");
 
/* interface */
DECLAR ("clk", ":1", "B", IN , "" , "" );
DECLAR ("rst", ":1", "B", IN , "" , "" );
DECLAR ( "ld", ":1", "B", IN , "" , "" );
DECLAR ( "m", ":2", "X", IN , "63 downto 0", "" );
DECLAR ("init", ":2", "B", IN , "" , "" );
DECLAR ( "md", ":2", "X", OUT, "63 downto 0", "" );
DECLAR ( "v", ":1", "B", OUT, "" , "" );
//DECLAR ("ctr2p", ":1", "X", OUT, " 3 downto 0", "" );
//DECLAR ("ctr3p", ":1", "X", OUT, " 5 downto 0", "" );
//DECLAR ("w_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("k_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("a_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("b_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("c_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("d_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("e_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("f_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("g_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("h_prb", ":2", "X", OUT, "31 downto 0", "" );
DECLAR ("vss", ":1", "B", IN , "" , "" );
DECLAR ("vdd", ":1", "B", IN , "" , "" );
 
AFFECT ("0", "vss", "0b0");
AFFECT ("0", "vdd", "0b1");
 
AFFECT ( "0", "rst", "0b1");
AFFECT ( "0", "clk", "0b0");
AFFECT ( "0", "ld", "0b0");
AFFECT ( "0", "m", "0x0000000000000000");
AFFECT ( "0","init", "0b0");
AFFECT ("+100", "clk", "0b1");
AFFECT ("+100", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
AFFECT ( "+0", "ld", "0b1");
AFFECT ( "+0","init", "0b1");
 
AFFECT ( "+0", "m", "0x6162638000000000");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
AFFECT ( "+0", "m", "0x0000000000000000");
i=1;
for (;i<0xf; i++)
{
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
}
AFFECT ( "+0", "m", "0x0000000000000018");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
i++;
AFFECT ( "+0", "m", "0x0000000000000000");
AFFECT ( "+0", "ld", "0b0");
AFFECT ( "+0","init", "0b0");
 
for (; i<0x5f+1; i++)
{
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
}
 
AFFECT ("+100", "clk", "0b1");
AFFECT ("+100", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
AFFECT ( "+0", "ld", "0b1");
AFFECT ( "+0","init", "0b1");
 
AFFECT ( "+0", "m", "0x6162636465666768");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6263646566676869");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x636465666768696a");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6465666768696a6b");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x65666768696a6b6c");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x666768696a6b6c6d");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6768696a6b6c6d6e");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x68696a6b6c6d6e6f");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x696a6b6c6d6e6f70");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6a6b6c6d6e6f7071");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6b6c6d6e6f707172");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6c6d6e6f70717273");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6d6e6f7071727374");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6e6f707172737475");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x8000000000000000");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x0000000000000000");
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x0000000000000000");
AFFECT ( "+0", "ld", "0b0");
AFFECT ( "+0","init", "0b0");
 
for (; i<0xaf+1; i++)
{
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
}
 
for (; i<0xbf;i++)
{
AFFECT ( "+0", "ld", "0b1");
AFFECT ("+100", "clk", "0b1");
AFFECT ("+100", "clk", "0b0");
}
 
AFFECT ( "+0", "m", "0x0000000000000380");
AFFECT ("+100", "clk", "0b1");
AFFECT ("+100", "clk", "0b0");
AFFECT ( "+0", "m", "0x0000000000000000");
AFFECT ( "+0", "ld", "0b0");
 
for (; i<0x11f+1; i++)
{
AFFECT ("+100", "clk", "0b1" );
AFFECT ("+100", "clk", "0b0" );
}
 
SAV_GENPAT ();
}
 
/sha512/c8b.vhdl
0,0 → 1,55
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
entity c8b is
port (
cnt : out bit_vector ( 7 downto 0);
clk : in bit;
rst : in bit
);
end c8b;
 
architecture phy of c8b is
signal sum : bit_vector ( 7 downto 0); -- sum
signal cr : bit_vector ( 7 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(7 downto 1) <= ( ((sum(6 downto 0) and B"0000001") or (sum(6 downto 0) and cr(6 downto 0))) or (B"0000001" and cr(6 downto 0)) );
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= B"00000000";
else
sum <= ((sum xor B"00000001") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha512/romk.c
0,0 → 1,38
#include <stdio.h>
#include "genpat.h"
 
char *inttostr(entier)
int entier;
{
char *str;
str = (char *) mbkalloc (32 * sizeof (char));
sprintf (str, "%d",entier);
return(str);
}
 
main ()
{
int i;
int cur_vect = 0;
 
DEF_GENPAT("romk");
SETTUNIT("ns");
 
/* interface */
DECLAR ("addr",":2", "X", IN , "6 downto 0", "" );
DECLAR ("k" , ":2", "X", OUT, "63 downto 0", "" );
DECLAR ("vss", ":1", "B", IN , "" , "" );
DECLAR ("vdd", ":1", "B", IN , "" , "" );
 
AFFECT ("0", "vss", "0b0");
AFFECT ("0", "vdd", "0b1");
AFFECT ("0","addr", "0b000000");
 
for (i=1; i<0x80; i++) {
AFFECT ("+10", "addr", inttostr(i%0x40) );
cur_vect++;
}
 
SAV_GENPAT ();
}
 
/sha512/c8b.c
0,0 → 1,45
#include <stdio.h>
#include "genpat.h"
 
char *inttostr(entier)
int entier;
{
char *str;
str = (char *) mbkalloc (32 * sizeof (char));
sprintf (str, "%d",entier);
return(str);
}
 
main ()
{
int i;
 
DEF_GENPAT("c8b");
SETTUNIT("ns");
 
/* interface */
DECLAR ("clk", ":1", "B", IN , "" , "" );
DECLAR ("rst", ":1", "B", IN , "" , "" );
DECLAR ("cnt", ":2", "X", OUT, "7 downto 0", "" );
//DECLAR ("c8b.sum",":2","X",REGISTER,"7 downto 0","");
//DECLAR ("c8b.cr" ,":2","X",SIGNAL ,"7 downto 0","");
DECLAR ("vss", ":1", "B", IN , "" , "" );
DECLAR ("vdd", ":1", "B", IN , "" , "" );
 
AFFECT ("0", "vss", "0b0");
AFFECT ("0", "vdd", "0b1");
 
AFFECT ( "0", "rst", "0b1");
AFFECT ( "0", "clk", "0b0");
AFFECT ("+10", "clk", "0b1");
AFFECT ("+10", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
 
for (i=1; i<256; i++) {
AFFECT ("+10", "clk", "0b1" );
AFFECT ("+10", "clk", "0b0" );
}
 
SAV_GENPAT ();
}
 
/sha512/Makefile
0,0 → 1,76
VASYFLAGS = -V -B -I vhdl -a -p -o
BOOMFLAGS = -VP
BOOGFLAGS =
LOONFLAGS =
OCPFLAGS = -v
NEROFLAGS = -V -G -6 -p
DRUCFLAGS =
S2RFLAGS = -v
OCP = ocp
NERO = nero
DRUC = druc
S2R = s2r
VASY = vasy
BOOM = boom
GENPAT = genpat -v
BOOG = boog
LOON = loon
RM = /bin/rm -vf
X2Y = x2y
FLATLO = flatlo
X2YFLAGS = vst vst
FLATLOFLAGS = -r
TOUCH = touch
 
# Set-up TARGET variable respectively
%.ap: TARGET = $(subst .ap,, $@)
%.pat: TARGET = $(subst .pat,, $@)
%.cif: TARGET = $(subst .cif,, $@)
%.vst: TARGET = $(subst .vst,, $@)
%.flt: TARGET = $(subst .flt,, $@)
%.sflt: TARGET = $(subst .sflt,, $@)
%.flatten: TARGET = $(subst .flatten,, $@)
 
all:
 
%.vbe: %.vhdl
@$(VASY) $(VASYFLAGS) $<
 
%.vst: %.vbe
@$(BOOM) $(BOOMFLAGS) $(TARGET) $(TARGET)_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET)_o.*
 
%.sflt: %.vbe
# @$(BOOM) $(BOOMFLAGS) $(TARGET)_model $(TARGET)_model_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_model
# @$(BOOG) $(BOOGFLAGS) $(TARGET)_model_o
# @$(LOON) $(LOONFLAGS) $(TARGET)_model_o $(TARGET)_model
-$(RM) $(TARGET)_model_o.*
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)
# @$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
# @$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
@$(TOUCH) $@
 
%.flt: %.vbe
@$(BOOM) $(BOOMFLAGS) $(TARGET)_model $(TARGET)_model_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_model_o
@$(LOON) $(LOONFLAGS) $(TARGET)_model_o $(TARGET)_model
-$(RM) $(TARGET)_model_o.*
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
@$(TOUCH) $@
 
%.flatten: %.vst
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
 
clean:
@rm -vf *.dat *.gpl *.vhd *.vbe *.boom *.vst *.xsc *.ap *.cif *.drc done.* *.flt *.sflt *_syn.pat *_sim.pat
/sha256/c4b.vhdl
0,0 → 1,55
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
entity c4b is
port (
cnt : out bit_vector ( 3 downto 0);
clk : in bit;
rst : in bit
);
end c4b;
 
architecture phy of c4b is
signal sum : bit_vector ( 3 downto 0); -- sum
signal cr : bit_vector ( 3 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(3 downto 1) <= ( ((sum(2 downto 0) and B"001") or (sum(2 downto 0) and cr(2 downto 0))) or (B"001" and cr(2 downto 0)) );
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= B"0000";
else
sum <= ((sum xor B"0001") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha256/romk.vhdl
0,0 → 1,111
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
entity romk is
port (
addr : in bit_vector ( 5 downto 0);
k : out bit_vector ( 31 downto 0)
);
end romk;
 
architecture phy of romk is
begin
with addr ( 5 downto 0) select
k <= X"428a2f98" when B"000000",
X"71374491" when B"000001",
X"b5c0fbcf" when B"000010",
X"e9b5dba5" when B"000011",
X"3956c25b" when B"000100",
X"59f111f1" when B"000101",
X"923f82a4" when B"000110",
X"ab1c5ed5" when B"000111",
 
X"d807aa98" when B"001000",
X"12835b01" when B"001001",
X"243185be" when B"001010",
X"550c7dc3" when B"001011",
X"72be5d74" when B"001100",
X"80deb1fe" when B"001101",
X"9bdc06a7" when B"001110",
X"c19bf174" when B"001111",
 
X"e49b69c1" when B"010000",
X"efbe4786" when B"010001",
X"0fc19dc6" when B"010010",
X"240ca1cc" when B"010011",
X"2de92c6f" when B"010100",
X"4a7484aa" when B"010101",
X"5cb0a9dc" when B"010110",
X"76f988da" when B"010111",
 
X"983e5152" when B"011000",
X"a831c66d" when B"011001",
X"b00327c8" when B"011010",
X"bf597fc7" when B"011011",
X"c6e00bf3" when B"011100",
X"d5a79147" when B"011101",
X"06ca6351" when B"011110",
X"14292967" when B"011111",
 
X"27b70a85" when B"100000",
X"2e1b2138" when B"100001",
X"4d2c6dfc" when B"100010",
X"53380d13" when B"100011",
X"650a7354" when B"100100",
X"766a0abb" when B"100101",
X"81c2c92e" when B"100110",
X"92722c85" when B"100111",
X"a2bfe8a1" when B"101000",
X"a81a664b" when B"101001",
X"c24b8b70" when B"101010",
X"c76c51a3" when B"101011",
X"d192e819" when B"101100",
X"d6990624" when B"101101",
X"f40e3585" when B"101110",
X"106aa070" when B"101111",
 
X"19a4c116" when B"110000",
X"1e376c08" when B"110001",
X"2748774c" when B"110010",
X"34b0bcb5" when B"110011",
X"391c0cb3" when B"110100",
X"4ed8aa4a" when B"110101",
X"5b9cca4f" when B"110110",
X"682e6ff3" when B"110111",
 
X"748f82ee" when B"111000",
X"78a5636f" when B"111001",
X"84c87814" when B"111010",
X"8cc70208" when B"111011",
X"90befffa" when B"111100",
X"a4506ceb" when B"111101",
X"bef9a3f7" when B"111110",
X"c67178f2" when B"111111";
end phy;
/sha256/sha256.vhdl
0,0 → 1,384
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
--
-- MaxMessage <= 2^64 bits
-- BlockSize == 512 bits
-- WordSize == 32 bits
-- MDigestSize == 256 bits
-- Security == 128 bits
--
-- SHLnx = (x<<n)
-- SHRnx = (x>>n)
-- ROTRnx = (x>>n) or (x<<w-n)
-- ROTLnx = (x<<n) or (x>>w-n)
--
-- f0 = ((x and y) xor (not(x) and z)) -- Ch(x,y,z)
-- f1 = ((x and y) xor (x and z) xor (y and z) -- Maj(x,y,z)
-- f2 = ROTR 2(x) xor ROTR 13(x) xor ROTR 22(x) -- Sigma0(x)
-- f3 = ROTR 6(x) xor ROTR 11(x) xor ROTR 25(x) -- Sigma1(x)
-- f4 = ROTR 7(x) xor ROTR 18(x) xor SHR 3(x) -- Tetha0(x)
-- f5 = ROTR 17(x) xor ROTR 19(x) xor SHR 10(x) -- Tetha1(x)
--
-- h0 = 0x6a09e667
-- h1 = 0xbb67ae85
-- h2 = 0x3c6ef372
-- h3 = 0xa54ff53a
-- h4 = 0x510e527f
-- h5 = 0x9b05688c
-- h6 = 0x1f83d9ab
-- h7 = 0x5be0cd19
--
-- k[0-63] looks like better implemented in ROM file
-- with 32 bit in each contants it would take
-- 64 x 32 bit storage which equal to
-- 2048 bit ROM
--
-- Step 1
-- W(t) = M(t) 0 <= t <= 15 -- we need 16x32 (512) bit registers
-- W(t) = f5(W(t-2)) + W(t-7) + f4(W(t-15)) + W(t-16); 16 <= t <= 79
-- W = f5(W( 1)) + W( 6) + f4(W( 14)) + W( 15); 16 <= t <= 79
--
-- Step 2
-- a = h0; b = h1; c = h2; d = h3; e = h4; f = h5; g = h6; h = h7;
--
-- Step 3
-- for t 0 step 1 to 63 do
-- T1= h + f3(e) + f0(e, f, g) + k(t) + W(t)
-- T2= f2(a) + f1(a, b, c)
-- h = g
-- g = f
-- f = e
-- e = d + T1
-- d = c
-- c = b
-- b = a
-- a = T1 + T2
--
-- Step 4
-- H0 = a + h0;
-- H1 = b + h1;
-- H2 = c + h2;
-- H3 = d + h3;
-- H4 = e + H4;
-- H5 = f + H5;
-- H6 = g + H6;
-- H7 = h + H7;
--
-- 31 63 95 127 159 191 223 255 287 319 351 383 415 447 479 511
-- 0 32 64 96 128 160 192 224 256 288 320 352 384 416 448 480 512
-- 0 1 2 3 4 5 6 7 8 9 a b c d e f
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
 
entity sha256 is
port(
m : in bit_vector ( 31 downto 0); -- 32 bit data path require 16 clock to load all 512 bits of each block
init : in bit; -- initial message
ld : in bit; -- load signal
md : out bit_vector ( 31 downto 0); -- 5 clock after active valid signal is the message hash result
--probe
--a_prb : out bit_vector ( 31 downto 0);
--b_prb : out bit_vector ( 31 downto 0);
--c_prb : out bit_vector ( 31 downto 0);
--d_prb : out bit_vector ( 31 downto 0);
--e_prb : out bit_vector ( 31 downto 0);
--f_prb : out bit_vector ( 31 downto 0);
--g_prb : out bit_vector ( 31 downto 0);
--h_prb : out bit_vector ( 31 downto 0);
--k_prb : out bit_vector ( 31 downto 0);
--w_prb : out bit_vector ( 31 downto 0);
--ctr2p : out bit_vector ( 3 downto 0);
--ctr3p : out bit_vector ( 5 downto 0);
--sc_pr : out bit_vector ( 1 downto 0);
--probe
v : out bit; -- hash output valid signal one clock advance
clk : in bit; -- master clock signal
rst : in bit -- master reset signal
);
end sha256;
 
architecture phy of sha256 is
 
component c4b
port (
cnt : out bit_vector ( 3 downto 0);
clk : in bit;
rst : in bit
);
end component;
 
component c6b
port (
cnt : out bit_vector ( 5 downto 0);
clk : in bit;
rst : in bit
);
end component;
 
component romk
port (
addr : in bit_vector ( 5 downto 0);
k : out bit_vector ( 31 downto 0)
);
end component;
 
signal ih : bit_vector ( 31 downto 0);
signal h0 : bit_vector ( 31 downto 0);
signal h1 : bit_vector ( 31 downto 0);
signal h2 : bit_vector ( 31 downto 0);
signal h3 : bit_vector ( 31 downto 0);
signal h4 : bit_vector ( 31 downto 0);
signal h5 : bit_vector ( 31 downto 0);
signal h6 : bit_vector ( 31 downto 0);
signal h7 : bit_vector ( 31 downto 0);
 
signal k : bit_vector ( 31 downto 0);
 
signal im : bit_vector ( 31 downto 0);
signal iw : bit_vector ( 31 downto 0);
signal w : bit_vector ( 31 downto 0); -- current working register
signal w0 : bit_vector (511 downto 0); -- working register 1
 
signal a : bit_vector ( 31 downto 0); -- a register
signal b : bit_vector ( 31 downto 0); -- b register
signal c : bit_vector ( 31 downto 0); -- c register
signal d : bit_vector ( 31 downto 0); -- d register
signal e : bit_vector ( 31 downto 0); -- e register
signal f : bit_vector ( 31 downto 0); -- f register
signal g : bit_vector ( 31 downto 0); -- g register
signal h : bit_vector ( 31 downto 0); -- h register
 
signal f0 : bit_vector ( 31 downto 0);
signal f1 : bit_vector ( 31 downto 0);
signal f2 : bit_vector ( 31 downto 0);
signal f3 : bit_vector ( 31 downto 0);
signal f4 : bit_vector ( 31 downto 0);
signal f5 : bit_vector ( 31 downto 0);
 
signal ctr2 : bit_vector ( 3 downto 0); -- 4 bit counter (zero to 16)
signal ctr2_rst: bit;
signal ctr3 : bit_vector ( 5 downto 0); -- 6 bit counter (zero to 64)
signal ctr3_rst: bit;
 
signal vld : bit;
signal nld : bit;
signal ild : bit;
signal ild_rst : bit;
 
begin
 
ct2 : c4b
port map (
cnt => ctr2,
clk => clk,
rst => ctr2_rst
);
ct3 : c6b
port map (
cnt => ctr3,
clk => clk,
rst => ctr3_rst
);
rom0 : romk
port map (
addr => ctr3,
k => k
);
 
--probe signal
--a_prb <= a;
--b_prb <= b;
--c_prb <= c;
--d_prb <= d;
--e_prb <= e;
--f_prb <= e;
--g_prb <= e;
--h_prb <= e;
--k_prb <= k;
--w_prb <= w;
--ctr2p <= ctr2;
--ctr3p <= ctr3;
--probe signal
 
--persistent connection
 
--f0 == ((x and y) xor (not(x) and z)) -- f0(e, f, g)
f0 <= ((e and f) xor (not(e) and g));
--f1 == ((x and y) xor (x and z) xor (y and z) -- f1(a, b, c)
f1 <= ((a and b) xor (a and c) xor (b and c));
--f2 == ROTR 2(x) xor ROTR 13(x) xor ROTR 22(x) -- f2(a)
f2 <= (a ( 1 downto 0) & a ( 31 downto 2)) xor
(a ( 12 downto 0) & a ( 31 downto 13)) xor
(a ( 21 downto 0) & a ( 31 downto 22));
--f3 == ROTR 6(x) xor ROTR 11(x) xor ROTR 25(x) -- f3(e)
f3 <= (e ( 5 downto 0) & e ( 31 downto 6)) xor
(e ( 10 downto 0) & e ( 31 downto 11)) xor
(e ( 24 downto 0) & e ( 31 downto 25));
--f4 == ROTR 7(x) xor ROTR 18(x) xor SHR 3(x) -- w0(479 downto 448)
f4 <= (w0(454 downto 448) & w0(479 downto 455)) xor
(w0(465 downto 448) & w0(479 downto 466)) xor
(B"000" & w0(479 downto 451));
--f5 == ROTR 17(x) xor ROTR 19(x) xor SHR 10(x) -- w0( 63 downto 32)
f5 <= (w0( 48 downto 32) & w0( 63 downto 49)) xor
(w0( 50 downto 32) & w0( 63 downto 51)) xor
(B"0000000000" & w0( 63 downto 42));
 
with ctr2( 2 downto 0) select -- omit bit 4
ih <= h0 when B"000",
h1 when B"001",
h2 when B"010",
h3 when B"011",
h4 when B"100",
h5 when B"101",
h6 when B"110",
h7 when B"111";
 
--W == f5(W( 1)) + W( 6) + f4(W( 14)) + W( 15); 16 <= t <= 79
--iw <= f5 + w0(223 downto 192) + f4 + w0(511 downto 480); -- FIXME this adder is very costly and NOT A PORTABLE CODE
iw <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(f5)) + unsigned(to_stdlogicvector(w0(223 downto 192))) + unsigned(to_stdlogicvector(f4)) + unsigned(to_stdlogicvector(w0(511 downto 480))) ));
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if (rst = '1') then
w <= (others => '0');
w0 <= (others => '0');
elsif (nld = '1') then -- 0 <= t <= 15 first 512 bit block
w <= im;
w0(511 downto 0) <= (w0(479 downto 0) & im);
else
w <= iw( 31 downto 0) ;
w0(511 downto 0) <= (w0(479 downto 0) & iw( 31 downto 0));
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if (rst = '1') then
ild <= '0';
nld <= '0';
im <= (others => '0');
else
ild <= nld;
nld <= ld;
im <= m;
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if ((ild_rst or rst) = '1') then
vld <= '0';
elsif (ctr3 = B"111111") then
vld <= '1';
else
vld <= '0';
end if;
end if;
end process;
 
ild_rst <= (ild xor ld) and ld;
--ctr2_rst <= ild_rst or rst or vld or (ctr2 = B"0111"); -- set to count to 7 ( 8 clock)
ctr2_rst <= ild_rst or rst or vld or not(ctr2(3) or not(ctr2(2)) or not(ctr2(1)) or not(ctr2(0)));
ctr3_rst <= ild_rst or rst;-- (ctr3 = B"010011"); -- set to count to 63 ( 64 clock)
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if (init = '1') or (rst = '1') then
h0 <= X"6a09e667";
h1 <= X"bb67ae85";
h2 <= X"3c6ef372";
h3 <= X"a54ff53a";
h4 <= X"510e527f";
h5 <= X"9b05688c";
h6 <= X"1f83d9ab";
h7 <= X"5be0cd19";
elsif (vld = '1') then -- FIXME this adder is very costly and NOT A PORTABLE CODE
h0 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(a)) + unsigned(to_stdlogicvector(h0)) ));
h1 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(b)) + unsigned(to_stdlogicvector(h1)) ));
h2 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(c)) + unsigned(to_stdlogicvector(h2)) ));
h3 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(d)) + unsigned(to_stdlogicvector(h3)) ));
h4 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(e)) + unsigned(to_stdlogicvector(h4)) ));
h5 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(f)) + unsigned(to_stdlogicvector(h5)) ));
h6 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(g)) + unsigned(to_stdlogicvector(h6)) ));
h7 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(h)) + unsigned(to_stdlogicvector(h7)) ));
-- h0 <= a + h0;
-- h1 <= b + h1;
-- h2 <= c + h2;
-- h3 <= d + h3;
-- h4 <= e + h4;
-- h5 <= f + h5;
-- h6 <= g + h6;
-- h7 <= h + h7;
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if ((ild_rst or rst) = '1') then
a <= h0;
b <= h1;
c <= h2;
d <= h3;
e <= h4;
f <= h5;
g <= h6;
h <= h7;
else -- FIXME this adder is very costly and NOT A PORTABLE CODE
-- T1 == h + f3(e) + f0(e, f, g) + k(t) + W(t)
-- T2 == f2(a) + f1(a, b, c)
h <= g;
g <= f;
f <= e;
-- e <= d + T1 ;
-- e <= d + h + f3 + f0 + k + w;
e <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(d)) + unsigned(to_stdlogicvector(h)) + unsigned(to_stdlogicvector(f3)) + unsigned(to_stdlogicvector(f0)) + unsigned(to_stdlogicvector(k)) + unsigned(to_stdlogicvector(w)) ));
d <= c;
c <= b;
b <= a;
-- a <= T1 + T2 ;
-- a <= h + f3 + f0 + k + w + f2 + f1;
a <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(h)) + unsigned(to_stdlogicvector(f3)) + unsigned(to_stdlogicvector(f0)) + unsigned(to_stdlogicvector(k)) + unsigned(to_stdlogicvector(w)) + unsigned(to_stdlogicvector(f2)) + unsigned(to_stdlogicvector(f1)) ));
end if;
end if;
end process;
 
md <= ih;
v <= vld;
 
end phy;
/sha256/c6b.vhdl
0,0 → 1,55
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
entity c6b is
port (
cnt : out bit_vector ( 5 downto 0);
clk : in bit;
rst : in bit
);
end c6b;
 
architecture phy of c6b is
signal sum : bit_vector ( 5 downto 0); -- sum
signal cr : bit_vector ( 5 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(5 downto 1) <= ( ((sum(4 downto 0) and B"00001") or (sum(4 downto 0) and cr(4 downto 0))) or (B"00001" and cr(4 downto 0)) );
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= B"000000";
else
sum <= ((sum xor B"000001") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha256/romk.c
0,0 → 1,38
#include <stdio.h>
#include "genpat.h"
 
char *inttostr(entier)
int entier;
{
char *str;
str = (char *) mbkalloc (32 * sizeof (char));
sprintf (str, "%d",entier);
return(str);
}
 
main ()
{
int i;
int cur_vect = 0;
 
DEF_GENPAT("romk");
SETTUNIT("ns");
 
/* interface */
DECLAR ("addr",":2", "X", IN , "5 downto 0", "" );
DECLAR ("k" , ":2", "X", OUT, "31 downto 0", "" );
DECLAR ("vss", ":1", "B", IN , "" , "" );
DECLAR ("vdd", ":1", "B", IN , "" , "" );
 
AFFECT ("0", "vss", "0b0");
AFFECT ("0", "vdd", "0b1");
AFFECT ("0","addr", "0b000000");
 
for (i=1; i<0x80; i++) {
AFFECT ("+10", "addr", inttostr(i%0x40) );
cur_vect++;
}
 
SAV_GENPAT ();
}
 
/sha256/sha256.c
0,0 → 1,182
#include <stdio.h>
#include "genpat.h"
 
char *inttostr(entier)
int entier;
{
char *str;
str = (char *) mbkalloc (32 * sizeof (char));
sprintf (str, "%d",entier);
return(str);
}
 
main ()
{
int i;
 
DEF_GENPAT("sha256");
SETTUNIT("ns");
 
/* interface */
DECLAR ("clk", ":1", "B", IN , "" , "" );
DECLAR ("rst", ":1", "B", IN , "" , "" );
DECLAR ( "ld", ":1", "B", IN , "" , "" );
DECLAR ( "m", ":2", "X", IN , "31 downto 0", "" );
DECLAR ("init", ":2", "B", IN , "" , "" );
DECLAR ( "md", ":2", "X", OUT, "31 downto 0", "" );
DECLAR ( "v", ":1", "B", OUT, "" , "" );
//DECLAR ("ctr2p", ":1", "X", OUT, " 3 downto 0", "" );
//DECLAR ("ctr3p", ":1", "X", OUT, " 5 downto 0", "" );
//DECLAR ("w_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("k_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("a_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("b_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("c_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("d_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("e_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("f_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("g_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("h_prb", ":2", "X", OUT, "31 downto 0", "" );
DECLAR ("vss", ":1", "B", IN , "" , "" );
DECLAR ("vdd", ":1", "B", IN , "" , "" );
 
AFFECT ("0", "vss", "0b0");
AFFECT ("0", "vdd", "0b1");
 
AFFECT ( "0", "rst", "0b1");
AFFECT ( "0", "clk", "0b0");
AFFECT ( "0", "ld", "0b0");
AFFECT ( "0", "m", "0x00000000");
AFFECT ( "0","init", "0b0");
AFFECT ("+50", "clk", "0b1");
AFFECT ("+50", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
AFFECT ( "+0", "ld", "0b1");
AFFECT ( "+0","init", "0b1");
 
AFFECT ( "+0", "m", "0x61626380");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
AFFECT ( "+0", "m", "0x00000000");
i=1;
for (;i<0xf; i++)
{
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
}
AFFECT ( "+0", "m", "0x00000018");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
i++;
AFFECT ( "+0", "m", "0x00000000");
AFFECT ( "+0", "ld", "0b0");
AFFECT ( "+0","init", "0b0");
 
for (; i<0x5f+1; i++)
{
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
}
 
AFFECT ("+50", "clk", "0b1");
AFFECT ("+50", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
AFFECT ( "+0", "ld", "0b1");
AFFECT ( "+0","init", "0b1");
 
AFFECT ( "+0", "m", "0x61626364");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x62636465");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x63646566");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x64656667");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x65666768");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x66676869");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6768696a");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x68696a6b");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x696a6b6c");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6a6b6c6d");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6b6c6d6e");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6c6d6e6f");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6d6e6f70");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6e6f7071");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x80000000");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x00000000");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x00000000");
AFFECT ( "+0", "ld", "0b0");
AFFECT ( "+0","init", "0b0");
 
for (; i<0xaf+1; i++)
{
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
}
 
for (; i<0xbf;i++)
{
AFFECT ( "+0", "ld", "0b1");
AFFECT ("+50", "clk", "0b1");
AFFECT ("+50", "clk", "0b0");
}
 
AFFECT ( "+0", "m", "0x000001c0");
AFFECT ("+50", "clk", "0b1");
AFFECT ("+50", "clk", "0b0");
AFFECT ( "+0", "m", "0x00000000");
AFFECT ( "+0", "ld", "0b0");
 
for (; i<0x11f+1; i++)
{
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
}
 
SAV_GENPAT ();
}
 
/sha256/Makefile
0,0 → 1,76
VASYFLAGS = -V -B -I vhdl -a -p -o
BOOMFLAGS = -VP
BOOGFLAGS =
LOONFLAGS =
OCPFLAGS = -v
NEROFLAGS = -V -G -6 -p
DRUCFLAGS =
S2RFLAGS = -v
OCP = ocp
NERO = nero
DRUC = druc
S2R = s2r
VASY = vasy
BOOM = boom
GENPAT = genpat -v
BOOG = boog
LOON = loon
RM = /bin/rm -vf
X2Y = x2y
FLATLO = flatlo
X2YFLAGS = vst vst
FLATLOFLAGS = -r
TOUCH = touch
 
# Set-up TARGET variable respectively
%.ap: TARGET = $(subst .ap,, $@)
%.pat: TARGET = $(subst .pat,, $@)
%.cif: TARGET = $(subst .cif,, $@)
%.vst: TARGET = $(subst .vst,, $@)
%.flt: TARGET = $(subst .flt,, $@)
%.sflt: TARGET = $(subst .sflt,, $@)
%.flatten: TARGET = $(subst .flatten,, $@)
 
all:
 
%.vbe: %.vhdl
@$(VASY) $(VASYFLAGS) $<
 
%.vst: %.vbe
@$(BOOM) $(BOOMFLAGS) $(TARGET) $(TARGET)_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET)_o.*
 
%.sflt: %.vbe
# @$(BOOM) $(BOOMFLAGS) $(TARGET)_model $(TARGET)_model_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_model
# @$(BOOG) $(BOOGFLAGS) $(TARGET)_model_o
# @$(LOON) $(LOONFLAGS) $(TARGET)_model_o $(TARGET)_model
-$(RM) $(TARGET)_model_o.*
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)
# @$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
# @$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
@$(TOUCH) $@
 
%.flt: %.vbe
@$(BOOM) $(BOOMFLAGS) $(TARGET)_model $(TARGET)_model_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_model_o
@$(LOON) $(LOONFLAGS) $(TARGET)_model_o $(TARGET)_model
-$(RM) $(TARGET)_model_o.*
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
@$(TOUCH) $@
 
%.flatten: %.vst
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
 
clean:
@rm -vf *.dat *.gpl *.vhd *.vbe *.boom *.vst *.xsc *.ap *.cif *.drc done.* *.flt *.sflt *_syn.pat *_sim.pat
/README.txt
0,0 → 1,5
Nugroho Free Hash Cores (NFHC)
 
* support SHA-1, SHA-256, SHA-512 (FIPS-180)
 
 
/sha1/sha1.pat
0,0 → 1,648
 
-- description generated by Pat driver
 
-- date : Sun Oct 4 19:23:31 2009
-- revision : v109
 
-- sequence : sha1
 
-- input / output list :
in clk B;;
in rst B;;
in ld B;;
in m (31 downto 0) X;;;
in init B;;;
out h (31 downto 0) X;;;
out v B;;
in vss B;;
in vdd B;;
 
begin
 
-- Pattern description :
 
-- c r l m i h v v v
-- l s d n s d
-- k t i s d
-- t
 
 
-- Beware : unprocessed patterns
 
< 0 ns> : 0 1 0 00000000 0 ?******** ?* 0 1 ;
< 50 ns> : 1 1 0 00000000 0 ?******** ?* 0 1 ;
< 100 ns> : 0 0 1 61626380 1 ?******** ?* 0 1 ;
< 150 ns> : 1 0 1 61626380 1 ?******** ?* 0 1 ;
< 200 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 250 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 300 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 350 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 400 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 450 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 500 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 550 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 600 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 650 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 700 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 750 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 800 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 850 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 900 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 950 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 1000 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 1050 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 1100 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 1150 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 1200 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 1250 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 1300 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 1350 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 1400 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 1450 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 1500 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 1550 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 1600 ns> : 0 0 1 00000018 1 ?******** ?* 0 1 ;
< 1650 ns> : 1 0 1 00000018 1 ?******** ?* 0 1 ;
< 1700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 1750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 1800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 1850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 1900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 1950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 2900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 2950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 3900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 3950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 4900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 4950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 5900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 5950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 6900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 6950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 7900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 7950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 8900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 8950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 9050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 9150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 9250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 9350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 9450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 9550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 9650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 9750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 9800 ns> : 0 0 1 61626364 1 ?******** ?* 0 1 ;
< 9850 ns> : 1 0 1 61626364 1 ?******** ?* 0 1 ;
< 9900 ns> : 0 0 1 62636465 1 ?******** ?* 0 1 ;
< 9950 ns> : 1 0 1 62636465 1 ?******** ?* 0 1 ;
< 10000 ns> : 0 0 1 63646566 1 ?******** ?* 0 1 ;
< 10050 ns> : 1 0 1 63646566 1 ?******** ?* 0 1 ;
< 10100 ns> : 0 0 1 64656667 1 ?******** ?* 0 1 ;
< 10150 ns> : 1 0 1 64656667 1 ?******** ?* 0 1 ;
< 10200 ns> : 0 0 1 65666768 1 ?******** ?* 0 1 ;
< 10250 ns> : 1 0 1 65666768 1 ?******** ?* 0 1 ;
< 10300 ns> : 0 0 1 66676869 1 ?******** ?* 0 1 ;
< 10350 ns> : 1 0 1 66676869 1 ?******** ?* 0 1 ;
< 10400 ns> : 0 0 1 6768696a 1 ?******** ?* 0 1 ;
< 10450 ns> : 1 0 1 6768696a 1 ?******** ?* 0 1 ;
< 10500 ns> : 0 0 1 68696a6b 1 ?******** ?* 0 1 ;
< 10550 ns> : 1 0 1 68696a6b 1 ?******** ?* 0 1 ;
< 10600 ns> : 0 0 1 696a6b6c 1 ?******** ?* 0 1 ;
< 10650 ns> : 1 0 1 696a6b6c 1 ?******** ?* 0 1 ;
< 10700 ns> : 0 0 1 6a6b6c6d 1 ?******** ?* 0 1 ;
< 10750 ns> : 1 0 1 6a6b6c6d 1 ?******** ?* 0 1 ;
< 10800 ns> : 0 0 1 6b6c6d6e 1 ?******** ?* 0 1 ;
< 10850 ns> : 1 0 1 6b6c6d6e 1 ?******** ?* 0 1 ;
< 10900 ns> : 0 0 1 6c6d6e6f 1 ?******** ?* 0 1 ;
< 10950 ns> : 1 0 1 6c6d6e6f 1 ?******** ?* 0 1 ;
< 11000 ns> : 0 0 1 6d6e6f70 1 ?******** ?* 0 1 ;
< 11050 ns> : 1 0 1 6d6e6f70 1 ?******** ?* 0 1 ;
< 11100 ns> : 0 0 1 6e6f7071 1 ?******** ?* 0 1 ;
< 11150 ns> : 1 0 1 6e6f7071 1 ?******** ?* 0 1 ;
< 11200 ns> : 0 0 1 80000000 1 ?******** ?* 0 1 ;
< 11250 ns> : 1 0 1 80000000 1 ?******** ?* 0 1 ;
< 11300 ns> : 0 0 1 00000000 1 ?******** ?* 0 1 ;
< 11350 ns> : 1 0 1 00000000 1 ?******** ?* 0 1 ;
< 11400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 11450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 11500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 11550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 11600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 11650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 11700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 11750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 11800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 11850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 11900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 11950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 12900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 12950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 13900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 13950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 14900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 14950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 15900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 15950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 16900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 16950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 17900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 17950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 18900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 18950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 19000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 19050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 19100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 19150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 19200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 19250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 19300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 19350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 19400 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 19450 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 19500 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 19550 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 19600 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 19650 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 19700 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 19750 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 19800 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 19850 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 19900 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 19950 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20000 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20050 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20100 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20150 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20200 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20250 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20300 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20350 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20400 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20450 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20500 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20550 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20600 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20650 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20700 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20750 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20800 ns> : 0 0 1 00000000 0 ?******** ?* 0 1 ;
< 20850 ns> : 1 0 1 00000000 0 ?******** ?* 0 1 ;
< 20900 ns> : 0 0 1 000001c0 0 ?******** ?* 0 1 ;
< 20950 ns> : 1 0 1 000001c0 0 ?******** ?* 0 1 ;
< 21000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 21900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 21950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 22900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 22950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 23900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 23950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 24900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 24950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 25900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 25950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 26900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 26950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 27900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 27950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 28900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 28950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29750 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29800 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29850 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 29900 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 29950 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 30000 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 30050 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 30100 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 30150 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 30200 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 30250 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 30300 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 30350 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 30400 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 30450 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 30500 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 30550 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 30600 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
< 30650 ns> : 1 0 0 00000000 0 ?******** ?* 0 1 ;
< 30700 ns> : 0 0 0 00000000 0 ?******** ?* 0 1 ;
 
end;
/sha1/c2b.vhdl
0,0 → 1,59
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
 
entity c2b is
port (
cnt : out bit_vector ( 1 downto 0);
clk : in bit;
rst : in bit
);
end c2b;
 
architecture phy of c2b is
signal sum : bit_vector ( 1 downto 0); -- sum
signal cr : bit_vector ( 1 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(1) <= sum(0);
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= B"00";
else
sum <= ((sum xor B"01") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha1/c4b.vhdl
0,0 → 1,55
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
entity c4b is
port (
cnt : out bit_vector ( 3 downto 0);
clk : in bit;
rst : in bit
);
end c4b;
 
architecture phy of c4b is
signal sum : bit_vector ( 3 downto 0); -- sum
signal cr : bit_vector ( 3 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(3 downto 1) <= ( ((sum(2 downto 0) and B"001") or (sum(2 downto 0) and cr(2 downto 0))) or (B"001" and cr(2 downto 0)) );
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= B"0000";
else
sum <= ((sum xor B"0001") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha1/c32b.vhdl
0,0 → 1,59
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
 
entity c32b is
port (
cnt : out bit_vector ( 31 downto 0);
clk : in bit;
rst : in bit
);
end c32b;
 
architecture phy of c32b is
signal sum : bit_vector ( 31 downto 0); -- sum
signal cr : bit_vector ( 31 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(31 downto 1) <= ( ((sum(30 downto 0) and B"0000000000000000000000000000001") or (sum(30 downto 0) and cr(30 downto 0))) or (B"0000000000000000000000000000001" and cr(30 downto 0)) );
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= X"00000000";
else
sum <= ((sum xor X"00000001") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha1/c6b.vhdl
0,0 → 1,55
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
entity c6b is
port (
cnt : out bit_vector ( 5 downto 0);
clk : in bit;
rst : in bit
);
end c6b;
 
architecture phy of c6b is
signal sum : bit_vector ( 5 downto 0); -- sum
signal cr : bit_vector ( 5 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(5 downto 1) <= ( ((sum(4 downto 0) and B"00001") or (sum(4 downto 0) and cr(4 downto 0))) or (B"00001" and cr(4 downto 0)) );
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= B"000000";
else
sum <= ((sum xor B"000001") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha1/c8b.vhdl
0,0 → 1,59
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
 
entity c8b is
port (
cnt : out bit_vector ( 7 downto 0);
clk : in bit;
rst : in bit
);
end c8b;
 
architecture phy of c8b is
signal sum : bit_vector ( 7 downto 0); -- sum
signal cr : bit_vector ( 7 downto 0); -- carry
begin
cr(0) <= '0'; -- LSB always zero
cr(7 downto 1) <= ( ((sum(6 downto 0) and B"0000001") or (sum(6 downto 0) and cr(6 downto 0))) or (B"0000001" and cr(6 downto 0)) );
process (clk)
begin
if (clk = '1' and clk'event) then
if (rst = '1') then
sum <= B"00000000";
else
sum <= ((sum xor B"00000001") xor cr); -- sum = ((addend xor augend) xor carry)
end if;
end if;
end process;
cnt <= sum;
end phy;
/sha1/sha1.vhdl
0,0 → 1,330
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
--
-- MaxMessage <= 2^64 bits
-- BlockSize == 512 bits
-- WordSize == 32 bits
-- MDigestSize == 160 bits
-- Security == 128 bits
--
-- SHLnx = (x<<n)
-- SHRnx = (x>>n)
-- ROTRnx = (x>>n) or (x<<w-n)
-- ROTLnx = (x<<n) or (x>>w-n)
--
-- f = ((x and y) xor (not(x) and z)) 0 <= t <= 19
-- f = (x xor y xor z) 20 <= t <= 39
-- f = ((x and y) xor (x and z) xor (y and z) 40 <= t <= 59
-- f = (x xor y xor z) 60 <= t <= 79
--
-- h0 = 0x67452301
-- h1 = 0xefcdab89
-- h2 = 0x98badcfe
-- h3 = 0x10325476
-- h4 = 0xc3d2e1f0
--
-- k0 = 0x5a827999 0 <= t <= 19
-- k1 = 0x6ed9eba1 20 <= t <= 39
-- k2 = 0x8f1bbcdc 40 <= t <= 59
-- k3 = 0xca62c1d6 60 <= t <= 79
--
-- Step 1
-- W(t) = M(t) 0 <= t <= 15 -- we need 16x32 (512) bit registers
-- W(t) = (W(t-3) xor W(t-8) xor W(t-14) xor W(t-16)) ROTL 1 16 <= t <= 79
-- W = (W( 2) xor W( 7) xor W( 13) xor W( 15)) ROTL 1; 16 <= t <= 79
--
-- Step 2
-- a = h0; b = h1; c = h2; d = h3; e = h4
--
-- Step 3
-- for t 0 step 1 to 79 do
-- T = ROTL5(a) xor f(b, c, d) xor e xor k(t) xor W(t)
-- e = d
-- d = c
-- c = ROTL30(b) -- c = ROTR2(b)
-- b = a
-- a = T
--
-- Step 4
-- H0 = a xor h0;
-- H1 = b xor h1;
-- H2 = c xor h2;
-- H3 = d xor h3;
-- H4 = e xor H4;
--
-- 31 63 95 127 159 191 223 255 287 319 351 383 415 447 479 511
-- 0 32 64 96 128 160 192 224 256 288 320 352 384 416 448 480 512
-- 0 1 2 3 4 5 6 7 8 9 a b c d e f
 
library ieee;
use ieee.std_logic_1164.all; -- std_logic stuff
use ieee.numeric_std.all; -- basic math for std_logic
 
entity sha1 is
port(
m : in bit_vector ( 31 downto 0); -- 32 bit data path require 16 clock to load all 512 bits of each block
init : in bit; -- initial message
ld : in bit; -- load signal
h : out bit_vector ( 31 downto 0); -- 5 clock after active valid signal is the message hash result
--probe
--a_prb : out bit_vector ( 31 downto 0);
--b_prb : out bit_vector ( 31 downto 0);
--c_prb : out bit_vector ( 31 downto 0);
--d_prb : out bit_vector ( 31 downto 0);
--e_prb : out bit_vector ( 31 downto 0);
--k_prb : out bit_vector ( 31 downto 0);
--w_prb : out bit_vector ( 31 downto 0);
--ctr2p : out bit_vector ( 3 downto 0);
--ctr3p : out bit_vector ( 5 downto 0);
--sc_pr : out bit_vector ( 1 downto 0);
--probe
v : out bit; -- hash output valid signal one clock advance
clk : in bit; -- master clock signal
rst : in bit -- master reset signal
);
end sha1;
 
architecture phy of sha1 is
 
component c4b
port (
cnt : out bit_vector ( 3 downto 0);
clk : in bit;
rst : in bit
);
end component;
 
component c6b
port (
cnt : out bit_vector ( 5 downto 0);
clk : in bit;
rst : in bit
);
end component;
 
signal ih : bit_vector ( 31 downto 0);
signal h0 : bit_vector ( 31 downto 0);
signal h1 : bit_vector ( 31 downto 0);
signal h2 : bit_vector ( 31 downto 0);
signal h3 : bit_vector ( 31 downto 0);
signal h4 : bit_vector ( 31 downto 0);
 
constant k0 : bit_vector ( 31 downto 0) := X"5a827999";
constant k1 : bit_vector ( 31 downto 0) := X"6ed9eba1";
constant k2 : bit_vector ( 31 downto 0) := X"8f1bbcdc";
constant k3 : bit_vector ( 31 downto 0) := X"ca62c1d6";
signal k : bit_vector ( 31 downto 0);
 
signal im : bit_vector ( 31 downto 0);
signal iw : bit_vector ( 31 downto 0);
signal w : bit_vector ( 31 downto 0); -- current working register
signal w0 : bit_vector (511 downto 0); -- working register 1
 
signal a : bit_vector ( 31 downto 0); -- a register
signal b : bit_vector ( 31 downto 0); -- b register
signal c : bit_vector ( 31 downto 0); -- c register
signal d : bit_vector ( 31 downto 0); -- d register
signal e : bit_vector ( 31 downto 0); -- e register
 
signal f : bit_vector ( 31 downto 0);
 
signal ctr2 : bit_vector ( 3 downto 0); -- 4 bit counter (zero to 16)
signal ctr2_rst: bit;
signal ctr3 : bit_vector ( 5 downto 0); -- 6 bit counter (zero to 64)
signal ctr3_rst: bit;
 
signal vld : bit;
signal nld : bit;
signal ild : bit;
signal ild_rst : bit;
 
signal sr : bit_vector ( 1 downto 0);
signal sc : bit_vector ( 1 downto 0);
 
begin
 
ct2 : c4b
port map (
cnt => ctr2,
clk => clk,
rst => ctr2_rst
);
ct3 : c6b
port map (
cnt => ctr3,
clk => clk,
rst => ctr3_rst
);
 
--probe signal
--a_prb <= a;
--b_prb <= b;
--c_prb <= c;
--d_prb <= d;
--e_prb <= e;
--k_prb <= k;
--w_prb <= w;
--sc_pr <= sc;
--ctr2p <= ctr2;
--ctr3p <= ctr3;
--probe signal
 
--persistent connection
with sc ( 1 downto 0) select
f <= ((b and c) xor (not(b) and d)) when B"00", -- 0 <= t <= 19
( b xor c xor d) when B"01", -- 20 <= t <= 39
((b and c) xor (b and d) xor (c and d)) when B"10", -- 40 <= t <= 59
( b xor c xor d) when B"11"; -- 60 <= t <= 79
with sc ( 1 downto 0) select
k <= k0 when B"00",
k1 when B"01",
k2 when B"10",
k3 when B"11";
with ctr2( 3 downto 0) select
ih <= h0 when B"0000",
h1 when B"0001",
h2 when B"0010",
h3 when B"0011",
h4 when B"0100",
(others => '0') when others;
 
--W = (W( 2) xor W( 7) xor W( 13) xor W( 15)) ROTL 1; 16 <= t <= 79
iw <= w0( 95 downto 64) xor w0(255 downto 224) xor w0(447 downto 416) xor w0(511 downto 480);
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if (rst = '1') then
w <= (others => '0');
w0 <= (others => '0');
elsif (nld = '1') then -- 0 <= t <= 15 first 512 bit block
w <= im;
w0(511 downto 0) <= (w0(479 downto 0) & im);
else -- ROTL1
w <= (iw( 30 downto 0) & iw( 31));
w0(511 downto 0) <= (w0(479 downto 0) & iw( 30 downto 0) & iw( 31));
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if (rst = '1') then
ild <= '0';
nld <= '0';
im <= (others => '0');
else
ild <= nld;
nld <= ld;
im <= m;
end if;
end if;
end process;
 
sr <= (sc(0) & '0');
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if ((ild_rst or rst) = '1') then
sc <= (others => '0');
elsif (ctr3 = B"010011") then
sc <= ((sc xor B"01") xor sr);
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if ((ild_rst or rst) = '1') then
vld <= '0';
elsif (ctr3 = B"010011") and (sc = B"11") then
vld <= '1';
else
vld <= '0';
end if;
end if;
end process;
 
ild_rst <= (ild xor ld) and ld;
--ctr2_rst <= ild_rst or rst or vld or (ctr2 = B"0100"); -- set to count to 4 ( 5 clock)
ctr2_rst <= ild_rst or rst or vld or not(ctr2(3) or not(ctr2(2)) or ctr2(1) or ctr2(0));
--ctr3_rst <= ild_rst or rst or (ctr3 = B"010011"); -- set to count to 19 ( 20 clock)
ctr3_rst <= ild_rst or rst or not(ctr3(5) or not(ctr3(4)) or ctr3(3) or ctr3(2) or not(ctr3(1)) or not(ctr3(0)));
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if (init = '1') or (rst = '1')then
h0 <= X"67452301";
h1 <= X"efcdab89";
h2 <= X"98badcfe";
h3 <= X"10325476";
h4 <= X"c3d2e1f0";
elsif (vld = '1') then -- FIXME this adder is very costly and NOT A PORTABLE CODE
h0 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(a)) + unsigned(to_stdlogicvector(h0)) ));
h1 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(b)) + unsigned(to_stdlogicvector(h1)) ));
h2 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(c)) + unsigned(to_stdlogicvector(h2)) ));
h3 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(d)) + unsigned(to_stdlogicvector(h3)) ));
h4 <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector(e)) + unsigned(to_stdlogicvector(h4)) ));
-- h0 <= a + h0;
-- h1 <= b + h1;
-- h2 <= c + h2;
-- h3 <= d + h3;
-- h4 <= e + h4;
end if;
end if;
end process;
 
process (clk)
begin
if ((clk = '1') and clk'event) then
if ((ild_rst or rst) = '1') then
a <= h0;
b <= h1;
c <= h2;
d <= h3;
e <= h4;
else
-- a <= (a(26 downto 0) & a(31 downto 27)) + f + e + k + w; -- ROTL5(a) -- FIXME this adder is very costly and NOT A PORTABLE CODE
a <= to_bitvector(std_logic_vector( unsigned(to_stdlogicvector( (a(26 downto 0) & a(31 downto 27)) )) + unsigned(to_stdlogicvector(f)) + unsigned(to_stdlogicvector(e)) + unsigned(to_stdlogicvector(k)) + unsigned(to_stdlogicvector(w)) ));
b <= a;
c <= (b( 1 downto 0) & b(31 downto 2)); -- ROTL30(b) -- ROTR2(b)
d <= c;
e <= d;
end if;
end if;
end process;
 
h <= ih;
v <= vld;
 
end phy;
/sha1/c32b.c
0,0 → 1,45
#include <stdio.h>
#include "genpat.h"
 
char *inttostr(entier)
int entier;
{
char *str;
str = (char *) mbkalloc (32 * sizeof (char));
sprintf (str, "%d",entier);
return(str);
}
 
main ()
{
int i;
 
DEF_GENPAT("c32b");
SETTUNIT("ns");
 
/* interface */
DECLAR ("clk", ":1", "B", IN , "" , "" );
DECLAR ("rst", ":1", "B", IN , "" , "" );
DECLAR ("cnt", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("c8b.sum",":2","X",REGISTER,"31 downto 0","");
//DECLAR ("c8b.cr" ,":2","X",SIGNAL ,"31 downto 0","");
DECLAR ("vss", ":1", "B", IN , "" , "" );
DECLAR ("vdd", ":1", "B", IN , "" , "" );
 
AFFECT ("0", "vss", "0b0");
AFFECT ("0", "vdd", "0b1");
 
AFFECT ( "0", "rst", "0b1");
AFFECT ( "0", "clk", "0b0");
AFFECT ("+10", "clk", "0b1");
AFFECT ("+10", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
 
for (i=1; i<0xffff+1; i++) {
AFFECT ("+10", "clk", "0b1" );
AFFECT ("+10", "clk", "0b0" );
}
 
SAV_GENPAT ();
}
 
/sha1/c8b.c
0,0 → 1,45
#include <stdio.h>
#include "genpat.h"
 
char *inttostr(entier)
int entier;
{
char *str;
str = (char *) mbkalloc (32 * sizeof (char));
sprintf (str, "%d",entier);
return(str);
}
 
main ()
{
int i;
 
DEF_GENPAT("c8b");
SETTUNIT("ns");
 
/* interface */
DECLAR ("clk", ":1", "B", IN , "" , "" );
DECLAR ("rst", ":1", "B", IN , "" , "" );
DECLAR ("cnt", ":2", "X", OUT, "7 downto 0", "" );
DECLAR ("c8b.sum",":2","X",REGISTER,"7 downto 0","");
DECLAR ("c8b.cr" ,":2","X",SIGNAL ,"7 downto 0","");
DECLAR ("vss", ":1", "B", IN , "" , "" );
DECLAR ("vdd", ":1", "B", IN , "" , "" );
 
AFFECT ("0", "vss", "0b0");
AFFECT ("0", "vdd", "0b1");
 
AFFECT ( "0", "rst", "0b1");
AFFECT ( "0", "clk", "0b0");
AFFECT ("+10", "clk", "0b1");
AFFECT ("+10", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
 
for (i=1; i<256; i++) {
AFFECT ("+10", "clk", "0b1" );
AFFECT ("+10", "clk", "0b0" );
}
 
SAV_GENPAT ();
}
 
/sha1/Makefile
0,0 → 1,76
VASYFLAGS = -V -B -I vhdl -a -p -o
BOOMFLAGS = -VP
BOOGFLAGS =
LOONFLAGS =
OCPFLAGS = -v
NEROFLAGS = -V -G -6 -p
DRUCFLAGS =
S2RFLAGS = -v
OCP = ocp
NERO = nero
DRUC = druc
S2R = s2r
VASY = vasy
BOOM = boom
GENPAT = genpat -v
BOOG = boog
LOON = loon
RM = /bin/rm -vf
X2Y = x2y
FLATLO = flatlo
X2YFLAGS = vst vst
FLATLOFLAGS = -r
TOUCH = touch
 
# Set-up TARGET variable respectively
%.ap: TARGET = $(subst .ap,, $@)
%.pat: TARGET = $(subst .pat,, $@)
%.cif: TARGET = $(subst .cif,, $@)
%.vst: TARGET = $(subst .vst,, $@)
%.flt: TARGET = $(subst .flt,, $@)
%.sflt: TARGET = $(subst .sflt,, $@)
%.flatten: TARGET = $(subst .flatten,, $@)
 
all:
 
%.vbe: %.vhdl
@$(VASY) $(VASYFLAGS) $<
 
%.vst: %.vbe
@$(BOOM) $(BOOMFLAGS) $(TARGET) $(TARGET)_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET)_o.*
 
%.sflt: %.vbe
# @$(BOOM) $(BOOMFLAGS) $(TARGET)_model $(TARGET)_model_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_model
# @$(BOOG) $(BOOGFLAGS) $(TARGET)_model_o
# @$(LOON) $(LOONFLAGS) $(TARGET)_model_o $(TARGET)_model
-$(RM) $(TARGET)_model_o.*
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)
# @$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
# @$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
@$(TOUCH) $@
 
%.flt: %.vbe
@$(BOOM) $(BOOMFLAGS) $(TARGET)_model $(TARGET)_model_o
@$(BOOG) $(BOOGFLAGS) $(TARGET)_model_o
@$(LOON) $(LOONFLAGS) $(TARGET)_model_o $(TARGET)_model
-$(RM) $(TARGET)_model_o.*
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
@$(TOUCH) $@
 
%.flatten: %.vst
@$(X2Y) $(X2YFLAGS) $(TARGET) $(TARGET)_m
@$(FLATLO) $(FLATLOFLAGS) $(TARGET)_m $(TARGET)_o
@$(LOON) $(LOONFLAGS) $(TARGET)_o $(TARGET)
-$(RM) $(TARGET){_o,m}.*
 
clean:
@rm -vf *.dat *.gpl *.vhd *.vbe *.boom *.vst *.xsc *.ap *.cif *.drc done.* *.flt *.sflt *_syn.pat *_sim.pat
/sha1/sha1.c
0,0 → 1,179
#include <stdio.h>
#include "genpat.h"
 
char *inttostr(entier)
int entier;
{
char *str;
str = (char *) mbkalloc (32 * sizeof (char));
sprintf (str, "%d",entier);
return(str);
}
 
main ()
{
int i;
 
DEF_GENPAT("sha1");
SETTUNIT("ns");
 
/* interface */
DECLAR ("clk", ":1", "B", IN , "" , "" );
DECLAR ("rst", ":1", "B", IN , "" , "" );
DECLAR ( "ld", ":1", "B", IN , "" , "" );
DECLAR ( "m", ":2", "X", IN , "31 downto 0", "" );
DECLAR ("init", ":2", "B", IN , "" , "" );
DECLAR ( "h", ":2", "X", OUT, "31 downto 0", "" );
DECLAR ( "v", ":1", "B", OUT, "" , "" );
//DECLAR ("ctr2p", ":1", "X", OUT, " 3 downto 0", "" );
//DECLAR ("ctr3p", ":1", "X", OUT, " 5 downto 0", "" );
//DECLAR ("sc_pr", ":1", "X", OUT, " 1 downto 0", "" );
//DECLAR ("a_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("b_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("c_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("d_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("e_prb", ":2", "X", OUT, "31 downto 0", "" );
//DECLAR ("w_prb", ":2", "X", OUT, "31 downto 0", "" );
DECLAR ("vss", ":1", "B", IN , "" , "" );
DECLAR ("vdd", ":1", "B", IN , "" , "" );
 
AFFECT ("0", "vss", "0b0");
AFFECT ("0", "vdd", "0b1");
 
AFFECT ( "0", "rst", "0b1");
AFFECT ( "0", "clk", "0b0");
AFFECT ( "0", "ld", "0b0");
AFFECT ( "0", "m", "0x00000000");
AFFECT ( "0","init", "0b0");
AFFECT ("+50", "clk", "0b1");
AFFECT ("+50", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
AFFECT ( "+0", "ld", "0b1");
AFFECT ( "+0","init", "0b1");
 
AFFECT ( "+0", "m", "0x61626380");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
AFFECT ( "+0", "m", "0x00000000");
i=1;
for (;i<0xf; i++)
{
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
}
AFFECT ( "+0", "m", "0x00000018");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
i++;
AFFECT ( "+0", "m", "0x00000000");
AFFECT ( "+0", "ld", "0b0");
AFFECT ( "+0","init", "0b0");
 
for (; i<0x5f+1; i++)
{
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
}
 
AFFECT ("+50", "clk", "0b1");
AFFECT ("+50", "clk", "0b0");
AFFECT ( "+0", "rst", "0b0");
AFFECT ( "+0", "ld", "0b1");
AFFECT ( "+0","init", "0b1");
 
AFFECT ( "+0", "m", "0x61626364");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x62636465");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x63646566");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x64656667");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x65666768");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x66676869");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6768696a");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x68696a6b");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x696a6b6c");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6a6b6c6d");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6b6c6d6e");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6c6d6e6f");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6d6e6f70");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x6e6f7071");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x80000000");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x00000000");
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
 
AFFECT ( "+0", "m", "0x00000000");
AFFECT ( "+0", "ld", "0b0");
AFFECT ( "+0","init", "0b0");
 
for (; i<0xaf+1; i++)
{
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
}
 
for (; i<0xbf;i++)
{
AFFECT ( "+0", "ld", "0b1");
AFFECT ("+50", "clk", "0b1");
AFFECT ("+50", "clk", "0b0");
}
 
AFFECT ( "+0", "m", "0x000001c0");
AFFECT ("+50", "clk", "0b1");
AFFECT ("+50", "clk", "0b0");
AFFECT ( "+0", "m", "0x00000000");
AFFECT ( "+0", "ld", "0b0");
 
for (; i<0x11f+1; i++)
{
AFFECT ("+50", "clk", "0b1" );
AFFECT ("+50", "clk", "0b0" );
}
 
SAV_GENPAT ();
}
 
/sha1/sha1f.vhdl
0,0 → 1,51
-- ------------------------------------------------------------------------
-- Copyright (C) 2010 Arif Endro Nugroho
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions
-- are met:
--
-- 1. Redistributions of source code must retain the above copyright
-- notice, this list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright
-- notice, this list of conditions and the following disclaimer in the
-- documentation and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY ARIF ENDRO NUGROHO "AS IS" AND ANY EXPRESS
-- OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL ARIF ENDRO NUGROHO BE LIABLE FOR ANY
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
-- ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
-- POSSIBILITY OF SUCH DAMAGE.
--
-- End Of License.
-- ------------------------------------------------------------------------
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
 
entity sha1f is
port (
x : in bit_vector ( 31 downto 0);
y : in bit_vector ( 31 downto 0);
z : in bit_vector ( 31 downto 0);
st : in bit_vector ( 1 downto 0); -- 4 states
f : out bit_vector ( 31 downto 0)
);
end sha1f;
 
architecture phy of sha1f is
begin
with st select
f <= ((x and y) xor (not(x) and z)) when B"00", -- 0 <= t <= 19
( x xor y xor z) when B"01", -- 20 <= t <= 39
((x and y) xor (x and z) xor (y and z)) when B"10", -- 40 <= t <= 59
( x xor y xor z) when B"11"; -- 60 <= t <= 79
end phy;

powered by: WebSVN 2.1.0

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