Examples of VHDL Descriptions
Examples of VHDL Descriptions
This file contains a selection of VHDL source files which serve to illustrate the diversity and power of the language when used to describe various types of hardware. The examples range from simple combinational logic, described in
terms of basic logic gates, to more complex systems, such as a behavioural model of a microprocessor and associated memory. All of the examples can be simulated using any IEEE compliant VHDL simulator and many can be
synthesised using current synthesis tools.
Use the hierarchical links below to navigate your way through the examples:
● Combinational Logic
● Counters
● Shift Registers
● Memory
● State Machines
● Registers
● Systems
● ADC and DAC
● Arithmetic
Combinational Logic
Counters
Shift Registers
Memory
State Machines
Systems
Arithmetic
Registers
● Universal Register
● Octal D-Type Register with 3-State Outputs
● Quad D-Type Flip-flop
● 8-bit Register with Synchronous Load and Clear
Universal Register
Description - This design is a universal register which can be used as a straightforward storage register, a bi-directional shift register, an up counter and a down counter. The register can be loaded from a set of parallel data inputs
and the mode is controlled by a 3-bit input. The 'termcnt' (terminal count) output goes high when the register contains zero.
LIBRARY ieee;
USE ieee.Std_logic_1164.ALL;
USE ieee.Std_logic_unsigned.ALL;
ENTITY unicntr IS
GENERIC(n : Positive := 8); --size of counter/shifter
PORT(clock, serinl, serinr : IN Std_logic; --serial inputs
mode : IN Std_logic_vector(2 DOWNTO 0); --mode control
datain : IN Std_logic_vector((n-1) DOWNTO 0); --parallel inputs
dataout : OUT Std_logic_vector((n-1) DOWNTO 0); --parallel outputs
termcnt : OUT Std_logic); --terminal count output
END unicntr;
ARCHITECTURE v1 OF unicntr IS
SIGNAL int_reg : Std_logic_vector((n-1) DOWNTO 0);
BEGIN
main_proc : PROCESS
BEGIN
WAIT UNTIL rising_edge(clock);
CASE mode IS
--reset
WHEN "000" => int_reg <= (OTHERS => '0');
--parallel load
WHEN "001" => int_reg <= datain;
--count up
WHEN "010" => int_reg <= int_reg + 1;
--count down
WHEN "011" => int_reg <= int_reg - 1;
--shift left
WHEN "100" => int_reg <= int_reg((n-2) DOWNTO 0) & serinl;
--shift right
WHEN "101" => int_reg <= serinr & int_reg((n-1) DOWNTO 1);
--do nothing
WHEN OTHERS => NULL;
END CASE;
END PROCESS;
Simple model of an Octal D-type register with three-state outputs using two concurrent statements.
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
ENTITY ttl374 IS
PORT(clock, oebar : IN std_logic;
data : IN std_logic_vector(7 DOWNTO 0);
qout : OUT std_logic_vector(7 DOWNTO 0));
END ENTITY ttl374;
-- 2 input exclusive or
-- Modeled at the RTL level.
entity x_or is
port (
in1 : in bit ;
in2 : in bit ;
out1 : out bit);
end x_or;
-- Exclusive or gate
-- modeled at the behavioral level.
entity x_or is
port (
in1 : in bit ;
in2 : in bit ;
out1 : out bit) ;
end x_or;
entity x_or is
port (
in1 : in bit ;
in2 : in bit ;
out1 : out bit) ;
end x_or;
entity and_gate is
port (
a : in bit ;
b : in bit ;
c : out bit) ;
end and_gate;
entity or_gate is
port (
d : in bit ;
e : in bit ;
f : out bit) ;
end or_gate;
entity inverter is
port (
g : in bit ;
h : out bit) ;
end inverter;
component and_gate
port (a, b : in bit; c : out bit) ;
end component;
component or_gate
port (d, e : in bit; f : out bit) ;
end component;
component inverter
port (g : in bit; h : out bit) ;
end component;
begin
u1: and_gate port map ( a => in1, b => t2, c => t4);
u4: or_gate port map ( d => t3, e => t4, f => out1);
end structural;
The entity declaration is followed by three alternative architectures which achieve the same functionality in different ways.
ENTITY maj IS
PORT(a,b,c : IN BIT; m : OUT BIT);
END maj;
BEGIN
--component instantiation statements.
--ports of component are mapped to signals
--within architecture by position.
gate1 : and2 PORT MAP (a, b, w1);
gate2 : and2 PORT MAP (b, c, w2);
gate3 : and2 PORT MAP (a, c, w3);
gate4 : or3 PORT MAP (w1, w2, w3, m);
Magnitude Comparator
ENTITY mag4comp IS
GENERIC(eqdel,gtdel,ltdel : TIME := 10 ns); --output delay parameters
PORT(a,b : IN BIT_VECTOR(3 DOWNTO 0); --input words, DOWNTO ordering
needed for comparison operators
aeqbin,agtbin,altbin : IN BIT; --expansion inputs
aeqbout,agtbout,altbout : OUT BIT); --outputs
END mag4comp;
The design entity shows the standard way of describing a register using a synchronous process, ie. a process containing a single wait statement which is triggered by a rising edge on the clock input.
library ieee;
use ieee.std_logic_1164.all;
entity reg8 is
port(clock, clear, load : in std_logic;
d : in std_logic_vector(7 downto 0);
q : out std_logic_vector(7 downto 0));
end entity reg8;
architecture v1 of reg8 is
begin
reg_proc : process
begin
wait until rising_edge(clock);
if clear = '1' then
q <= (others => '0');
elsif load = '1' then
q <= d;
end if;
end process;
end architecture v1;
The use of the std_logic literal '-' (don't care) is primarily for the synthesis tool. This example illustrates the use of the selected signal assignment.
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
ENTITY seg7dec IS
PORT(bcdin : IN std_logic_vector(3 DOWNTO 0);
segout : OUT std_logic_vector(6 DOWNTO 0));
END seg7dec;
This set of design units illustrates several features of the VHDL language including:
--------------------------------------------------------------
ENTITY inv IS
GENERIC(tplh,tphl,tplhe,tphle : TIME := 1 ns);
PORT(a : IN BIT; b : OUT BIT);
END inv;
COMPONENT inv
BEGIN
END structural;
-------------------------------------------------------------------
ENTITY dec2to4_stim IS
PORT(stimulus : OUT BIT_VECTOR(0 TO 2); response : IN BIT_VECTOR(0 TO 3));
END dec2to4_stim;
COMPONENT dec2to4
PORT(s0,s1,en : IN BIT; y0,y1,y2,y3 : OUT BIT);
END COMPONENT;
COMPONENT dec2to4_stim
PORT(stimulus : OUT BIT_VECTOR(0 TO 2); response : IN BIT_VECTOR(0 TO 3));
END COMPONENT;
BEGIN
END structural;
---------------------------------------------------------------
CONFIGURATION parts OF dec2to4_bench IS
FOR structural
END FOR;
END parts;
The first design entity is a T-type flip-flop. The second is an scalable synchronous binary up counter illustrating the use of the generate statement to produce regular structures of components.
library ieee;
use ieee.std_logic_1164.all;
entity tff is
port(clk, t, clear : in std_logic; q : buffer std_logic);
end tff;
architecture v1 of tff is
begin
process(clear, clk)
begin
if clear = '1' then
q <= '0';
elsif rising_edge(clk) then
if t = '1' then
q <= not q;
else
null;
end if;
end if;
end process;
end v1;
library ieee;
use ieee.std_logic_1164.all;
entity bigcntr is
generic(size : positive := 32);
port(clk, clear : in std_logic;
q : buffer std_logic_vector((size-1) downto 0));
end bigcntr;
architecture v1 of bigcntr is
component tff is
port(clk, t, clear : in std_logic; q : buffer std_logic);
end component;
begin
end v1;
ENTITY cntr3 IS
PORT(clock : IN BIT; count : OUT NATURAL);
END cntr3;
This counter uses a natural number to hold the count value and converts it into a bit_vector for output. Illustrates the use of a function.
ENTITY cntr4bit IS
PORT(reset,clock : IN BIT; count : OUT BIT_VECTOR(0 TO 3));
END cntr4bit;
BEGIN
--conditional natural signal assignment models counter
intcount <= 0 WHEN (reset = '1') ELSE
((intcount + 1) MOD 16) WHEN (clock'EVENT AND clock = '1')
ELSE intcount;
--interface function converts natural count to bit_vector count
count <= nat_to_bv(intcount,3);
END;
This example shows how a conditional signal assignment statement could be used to describe sequential logic (it is more common to use a process). The keyword 'unaffected' is equivalent to the 'null' statement in the sequential part
of the language. The model would work exactly the same without the clause 'else unaffected' attached to the end of the statement.
This example shows the use of the high impedance literal 'Z' provided by std_logic. The aggregate '(others => 'Z')' means all of the bits of B must be forced to 'Z'. Ports A and B must be resolved for this model to work correctly (hence std_logic rather than
std_ulogic).
library IEEE;
use IEEE.Std_logic_1164.all;
entity HCT245 is
port(A, B : inout std_logic_vector(7 downto 0);
DIR, GBAR : in std_logic);
end HCT245;
Quad 2-input OR
Hamming Encoder
A 4-bit Hamming Code encoder using concurrent assignments. The output vector is connected to the individual parity bits using an aggregate assignment.
ENTITY hamenc IS
PORT(datain : IN BIT_VECTOR(0 TO 3); --d0 d1 d2 d3
hamout : OUT BIT_VECTOR(0 TO 7)); --d0 d1 d2 d3 p0 p1 p2 p4
END hamenc;
BEGIN
--connect up outputs
hamout(4 TO 7) <= (p0, p1, p2, p4);
hamout(0 TO 3) <= datain(0 TO 3);
END ver2;
Hamming Decoder
This Hamming decoder accepts an 8-bit Hamming code (produced by the encoder above) and performs single error correction and double error detection.
ENTITY hamdec IS
PORT(hamin : IN BIT_VECTOR(0 TO 7); --d0 d1 d2 d3 p0 p1 p2 p4
dataout : OUT BIT_VECTOR(0 TO 3); --d0 d1 d2 d3
sec, ded, ne : OUT BIT); --diagnostic outputs
END hamdec;
BEGIN
PROCESS(hamin)
VARIABLE syndrome : BIT_VECTOR(3 DOWNTO 0);
BEGIN
END IF;
END PROCESS;
END ver1;
This example shows the use of the package 'std_logic_unsigned' . The minus operator '-' is overloaded by this package, thereby allowing an integer to be subracted from a std_logic_vector.
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
USE ieee.std_logic_unsigned.ALL;
ENTITY pldcntr8 IS
PORT (clk, load : IN Std_logic;
datain : IN Std_logic_vector(7 DOWNTO 0);
q : OUT Std_logic_vector(7 DOWNTO 0);
tc : OUT Std_logic);
END pldcntr8;
BEGIN
END using_std_logic;
Structural description of a 4-bit binary counter. The first two design entities describe a JK flip-flop and a 2-input AND gate respectively. These are then packaged together along with a signal named 'tied_high' into a package named
'jkpack'. The counter design uses the package 'jkpack', giving it access to the components and the signal declared within the package. The flip-flops and AND-gates are wired together to form a counter. Notice the use of the keyword
OPEN to indicate an open-cct output port.
ENTITY jkff IS
PORT(clock, j, k : IN BIT; q, qbar : BUFFER BIT);
END jkff;
BEGIN
END PROCESS;
END using_process;
ENTITY and_gate IS
PORT(a, b : IN BIT; f : OUT BIT);
END and_gate;
ARCHITECTURE simple OF and_gate IS
BEGIN
f <= a AND b AFTER 2 ns;
END simple;
PACKAGE jkpack IS
COMPONENT jkff
PORT(clock, j, k : IN BIT; q, qbar : BUFFER BIT);
END COMPONENT;
COMPONENT and_gate
PORT(a, b : IN BIT; f : OUT BIT);
END COMPONENT;
END jkpack;
USE work.jkpack.ALL;
ENTITY mod16_cntr IS
PORT(clock : IN BIT; count : BUFFER BIT_VECTOR(0 TO 3));
END mod16_cntr;
BEGIN
END net_list;
This design entity uses a single conditional signal assignment statement to describe a PRBSG register. The length of the register and the two tapping points are defined using generics. The '&' (aggregate) operator is used to form a
vector comprising the shifted contents of the regsiter combined with the XOR feedback which is clocked into the register on the rising edge.
ENTITY prbsgen IS
GENERIC(length : Positive := 8; tap1 : Positive := 8; tap2 : Positive := 4);
PORT(clk, reset : IN Bit; prbs : OUT Bit);
END prbsgen;
ARCHITECTURE v2 OF prbsgen IS
BEGIN
END v2;
architecture v1 of pelcross is
begin
end v1;
architecture v1 of peltest is
component pelcross is
port(clock, reset, pedestrian : in std_logic;
red, amber, green : out std_logic); --traffic lights
end component;
begin
--test inputs
process begin
pedestrian <= '0';
reset <= '1';
wait for 300 ms;
reset <= '0';
wait for 40000 ms;
pedestrian <= '1';
wait for 200 ms;
pedestrian <= '0';
wait;
end process;
end v1;
PACKAGE cpu8pac IS
--defining instruction set
--instruction format
-- 7----4|3--0|7----------0
-- opcode|page|[page offset]
--instructions which need an address are two bytes
--long all others are single byte
CONSTANT lda : BIT_VECTOR(3 DOWNTO 0) := "0001";
CONSTANT ldb : BIT_VECTOR(3 DOWNTO 0) := "0010";
CONSTANT sta : BIT_VECTOR(3 DOWNTO 0) := "0011";
CONSTANT stb : BIT_VECTOR(3 DOWNTO 0) := "0000";
CONSTANT jmp : BIT_VECTOR(3 DOWNTO 0) := "0100";
CONSTANT add : BIT_VECTOR(3 DOWNTO 0) := "0101";
CONSTANT subr : BIT_VECTOR(3 DOWNTO 0) := "0110";
CONSTANT inc : BIT_VECTOR(3 DOWNTO 0) := "0111";
CONSTANT dec : BIT_VECTOR(3 DOWNTO 0) := "1000";
CONSTANT land : BIT_VECTOR(3 DOWNTO 0) := "1001";
CONSTANT lor : BIT_VECTOR(3 DOWNTO 0) := "1010";
CONSTANT cmp : BIT_VECTOR(3 DOWNTO 0) := "1011";
CONSTANT lxor : BIT_VECTOR(3 DOWNTO 0) := "1100";
CONSTANT lita : BIT_VECTOR(3 DOWNTO 0) := "1101";
CONSTANT litb : BIT_VECTOR(3 DOWNTO 0) := "1110";
CONSTANT clra : BIT_VECTOR(3 DOWNTO 0) := "1111";
END cpu8pac;
-- package bv_math
--
-- Bit Vector support package:
--
-- Contains these functions:
-- The output length of the function is the same as the input length.
--
-- inc_bv - increment a bit vector. If function is assigned
-- to a signal within a clocked process, the result
-- will be an up counter. Will require one macrocell
-- for each bit.
--
-- dec_bv - decrement a bit vector. If function is assigned
-- to a signal within a clocked process, the result
-- will be a down counter. Will require one macrocell
-- for each bit.
--
-- "+" - regular addition function for two bit vectors.
-- "+" operator overloads the existing "+" operator
-- definition for arithmetic operations on integers.
-- Will require one macrocell for each bit. The output
-- is the same size as the input so there is no carry output.
-- If a carry out is required, the user should increase the
-- size of the input bit_vectors and use the MSB as the
-- carry bit. There is also no separate carry-in.
--
-- "-" - regular subtraction function for two bit vectors.
-- "-" operator overloads the existing "-" operator
-- definition for arithmetic operations on integers.
--
-- inv - unary invert for use in port maps and sequential
-- assignments. Overloaded for bit_vectors.
--
--
PACKAGE bv_math IS
FUNCTION inc_bv (a : BIT_VECTOR) RETURN BIT_VECTOR;
FUNCTION dec_bv (a : BIT_VECTOR) RETURN BIT_VECTOR;
FUNCTION "+" (a, b : BIT_VECTOR) RETURN BIT_VECTOR;
FUNCTION "+" (a : BIT_VECTOR; b : BIT) RETURN BIT_VECTOR;
FUNCTION "-" (a, b : BIT_VECTOR) RETURN BIT_VECTOR;
FUNCTION "-" (a : BIT_VECTOR; b : BIT) RETURN BIT_VECTOR;
FUNCTION inv (a : BIT) RETURN BIT;
FUNCTION inv (a : BIT_VECTOR) RETURN BIT_VECTOR;
END bv_math;
-- inc_bv
-- Increment Bit vector.
-- In: bit_vector.
-- Return: bit_vector.
--
FUNCTION inc_bv(a : BIT_VECTOR)RETURN BIT_VECTOR IS
VARIABLE s : BIT_VECTOR (a'RANGE);
VARIABLE carry : BIT;
BEGIN
carry := '1';
RETURN (s);
END inc_bv;
-- "+"
-- Add overload for:
-- In: two bit_vectors.
-- Return: bit_vector.
--
FUNCTION "+"(a, b : BIT_VECTOR)RETURN BIT_VECTOR IS
VARIABLE s : BIT_VECTOR (a'RANGE);
VARIABLE carry : BIT;
VARIABLE bi : integer; -- Indexes b.
BEGIN
ASSERT a'LENGTH <= 8 REPORT
"Addition OF vectors OF LENGTH > 8 may take exponential TIME."
SEVERITY WARNING;
carry := '0';
RETURN (s);
END "+"; -- Two bit_vectors.
-- "+"
-- Add overload for:
-- In: bit_vector and bit.
-- Return bit_vector.
--
FUNCTION "+"(a : BIT_VECTOR; b : BIT)RETURN BIT_VECTOR IS
VARIABLE s : BIT_VECTOR (a'RANGE);
VARIABLE carry : BIT;
BEGIN
carry := b;
RETURN (s);
END "+"; -- Bit_vector and bit.
-- dec_bv
-- Decrement Bit Vector
-- In: bit_vector.
-- Return: bit_vector.
--
FUNCTION dec_bv(a : BIT_VECTOR) RETURN BIT_VECTOR IS
VARIABLE s : BIT_VECTOR (a'RANGE);
VARIABLE borrow : BIT;
BEGIN
borrow := '1';
RETURN (s);
END dec_bv;
-- "-"
-- Subtract overload for:
borrow := '0';
borrow := (
(NOT (a(i)) AND borrow)
OR (b(bi) AND borrow)
OR (NOT (a(i)) AND b(bi))
);
END LOOP;
RETURN (s);
END "-"; -- two bit_vectors
-- "-"
-- Subtract overload for:
-- In: bit_vector, take away bit.
-- Return: bit_vector.
--
FUNCTION "-" (a : BIT_VECTOR; b : BIT) RETURN BIT_VECTOR IS
VARIABLE s : BIT_VECTOR (a'RANGE);
VARIABLE borrow : BIT;
BEGIN
borrow := b;
RETURN (s);
END "-";
-- inv
-- Invert bit.
--
FUNCTION inv (a : BIT) RETURN BIT IS
VARIABLE result : BIT;
BEGIN
result := NOT(a);
RETURN (result);
END inv; -- Invert bit.
-- inv
-- Invert bet_vector.
--
FUNCTION inv (a : BIT_VECTOR) RETURN BIT_VECTOR IS
VARIABLE result : BIT_VECTOR (a'RANGE);
BEGIN
FOR i IN a'RANGE LOOP
result(i) := NOT(a(i));
END LOOP;
RETURN (result);
END inv; -- Invert bit_vector.
END bv_math;
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
USE work.cpu8pac.ALL;
ENTITY rom256x8 IS
PORT(address : IN STD_LOGIC_VECTOR(7 DOWNTO 0);
csbar, oebar : IN STD_LOGIC;
data : OUT STD_LOGIC_VECTOR(7 DOWNTO 0));
END rom256x8;
--version 1 loads acca and accb from locations 254 and 256
--and exclusive or's the values and jumps back to repeat
ARCHITECTURE version1 OF rom256x8 IS
TYPE rom_array IS ARRAY (0 TO 255) OF BIT_VECTOR(7 DOWNTO 0);
CONSTANT rom_values : rom_array :=
(0 => clra & X"0",
1 => lda & X"0", --lda $FE
2 => X"fe",
3 => ldb & X"0", --ldb $FF
4 => X"ff",
5 => lxor & X"0", --lxor
6 => jmp & X"0", --jmp $001
7 => X"01",
254 => X"aa",
255 => X"55",
OTHERS => X"00");
BEGIN
PROCESS(address, csbar, oebar)
VARIABLE index : INTEGER := 0;
BEGIN
IF (csbar = '1' OR oebar = '1')
THEN data <= "ZZZZZZZZ";
ELSE
END IF;
END PROCESS;
END version1;
END IF;
END PROCESS;
END version2;
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
ENTITY ram16x8 IS
PORT(address : IN STD_LOGIC_VECTOR(3 DOWNTO 0);
csbar, oebar, webar : IN STD_LOGIC;
data : INOUT STD_LOGIC_VECTOR(7 DOWNTO 0));
END ram16x8;
BEGIN
IF rising_edge(webar) THEN
--write to ram on rising edge of write pulse
ram_store(index) := To_bitvector(data);
ELSIF oebar = '0' THEN
data <= To_StdlogicVector(ram_store(index));
ELSE
data <= "ZZZZZZZZ";
END IF;
ELSE
data <= "ZZZZZZZZ";
END IF;
END PROCESS;
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
USE work.bv_math.ALL;
USE work.cpu8pac.ALL;
ENTITY cpu IS
GENERIC(cycle_time : TIME := 200 ns); --must be divisible by 8
PORT(reset : IN std_logic;
memrd, memwr : OUT std_logic;
address : OUT std_logic_vector(11 DOWNTO 0);
data : INOUT std_logic_vector(7 DOWNTO 0));
END cpu;
BEGIN
clock_gen : PROCESS
BEGIN
clock <= '1','0' AFTER cycle_time/2;
WAIT FOR cycle_time;
END PROCESS;
main_sequence : PROCESS
BEGIN
--initialisation
memrd <= '1';
memwr <= '1';
pc := (OTHERS => '0');
address <= (OTHERS => 'Z');
data <= (OTHERS => 'Z');
WAIT UNTIL rising_edge(clock);
ELSE
--fetch phase
address <= To_StdlogicVector(pc);
WAIT FOR cycle_time/4;
memrd <= '0';
WAIT FOR cycle_time/2;
memrd <= '1';
--read instruction
inst_reg := To_bitvector(data(7 DOWNTO 4));
--load page address
mar(11 DOWNTO 8) := To_bitvector(data(3 DOWNTO 0));
--increment program counter
pc := inc_bv(pc);
--wait until end of cycle
WAIT UNTIL rising_edge(clock);
--execute
CASE inst_reg IS
WHEN add =>
--add and sub use overloaded functions from bv_math package
END version1;
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
ENTITY cpudemo IS
END cpudemo;
COMPONENT rom256x8
PORT(address : IN STD_LOGIC_VECTOR(7 DOWNTO 0);
csbar, oebar : IN STD_LOGIC;
data : OUT STD_LOGIC_VECTOR(7 DOWNTO 0));
END COMPONENT;
COMPONENT ram16x8
PORT(address : IN STD_LOGIC_VECTOR(3 DOWNTO 0);
csbar, oebar, webar : IN STD_LOGIC;
data : INOUT STD_LOGIC_VECTOR(7 DOWNTO 0));
END COMPONENT;
COMPONENT cpu
GENERIC(cycle_time : TIME := 200 ns); --must be divisible by 8
PORT(reset : IN std_logic;
memrd, memwr : OUT std_logic;
address : OUT std_logic_vector(11 DOWNTO 0);
data : INOUT std_logic_vector(7 DOWNTO 0));
END COMPONENT;
BEGIN
ram : ram16x8 PORT MAP(address(3 DOWNTO 0), ramenable, memrd, memwr, data);
END version1;
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
entity count49 is
port(clock, clear : in std_logic;
cnt1to49 : buffer std_logic_vector(7 downto 0));
end entity count49;
architecture v1 of count49 is
begin
count_proc : process
begin
wait until rising_edge(clock);
if (clear = '1') or (cnt1to49 = X"49") then
cnt1to49 <= (0 => '1', others => '0');
elsif cnt1to49(3 downto 0) = 9 then
cnt1to49(3 downto 0) <= (others => '0');
cnt1to49(7 downto 4) <= cnt1to49(7 downto 4) + 1;
else
cnt1to49(3 downto 0) <= cnt1to49(3 downto 0) + 1;
end if;
end process;
end architecture v1;
architecture v1 of lottreg is
begin
reg_proc : process
begin
wait until rising_edge(clock);
if clear = '1' then
q <= (others => '0');
elsif load = '1' then
q <= d;
end if;
Controller
type lott_state_type is (res, s1, s2, s3, s4, s5, s6, s7,
s8, s9, s10, s11, s12, s13, s14, s15, s16, s17, s18,
s19, s20, s21, s22, s23, s24, s25, s26, s27, s28);
begin
--next state process
fsm_state_reg : process
begin
wait until rising_edge(clock);
if reset = '1' then
lott_ps <= res;
else
lott_ps <= lott_ns;
end if;
end process;
component lottreg
port(clock, clear, load : in std_logic;
d : in std_logic_vector(7 downto 0);
q : out std_logic_vector(7 downto 0));
end component;
component count49
component lottcont2
port(clock, reset, next_no, match : in std_logic;
loadnum1, loadnum2, loadnum3, loadnum4,
loadnum5, loadnum6, sample : out std_logic;
seldisplay : out natural range 0 to 5;
numled : out std_logic_vector(1 to 6));
end component;
begin
counter : count49
port map (clock => clock, clear => reset, cnt1to49 => count);
sample_reg : lottreg
port map (clock => clock, clear => reset,
load => sample, d => count, q => samp_reg);
--number registers
numreg1 : lottreg port map
(clock => clock, clear => reset, load => loadnum1,
d => samp_reg, q => num_reg1);
numreg2 : lottreg port map
(clock => clock, clear => reset, load => loadnum2,
d => samp_reg, q => num_reg2);
numreg3 : lottreg port map
(clock => clock, clear => reset, load => loadnum3,
d => samp_reg, q => num_reg3);
numreg4 : lottreg port map
(clock => clock, clear => reset, load => loadnum4,
d => samp_reg, q => num_reg4);
numreg5 : lottreg port map
(clock => clock, clear => reset, load => loadnum5,
d => samp_reg, q => num_reg5);
numreg6 : lottreg port map
(clock => clock, clear => reset, load => loadnum6,
d => samp_reg, q => num_reg6);
segdec0 : seg7dec
port map (bcdin => display(3 downto 0), segout => seg0);
segdec1 : seg7dec
port map (bcdin => display(7 downto 4), segout => seg1);
controller : lottcont2
port map (clock => clock, reset => reset, next_no => next_no,
match => match, loadnum1 => loadnum1,
loadnum2 => loadnum2, loadnum3 => loadnum3,
loadnum4 => loadnum4, loadnum5 => loadnum5,
loadnum6 => loadnum6, sample => sample,
seldisplay => seldisplay,
numled => numled);
Booth Multiplier
BEGIN
END PROCESS;
END structural;
architecture V2 of FIFOMXN is
begin
Fifo_read : process
begin
wait until rising_edge(CLOCK);
if RESET = '1' then
Rdaddr <= 0;
Databuffer <= (others => '0');
elsif (Rdpulse = '1' and EMPTY = '0') then
Databuffer <= Fifo_memory(Rdaddr);
Rdaddr <= (Rdaddr + 1) mod m;
end if;
end process;
Fifo_write : process
end V2;
PACKAGE rompac IS
END rompac;
BEGIN
END PROCESS;
END behaviour;
ENTITY fsm IS
PORT(clock,x : IN BIT; z : OUT BIT);
END fsm;
-------------------------------------------------
ARCHITECTURE behaviour OF fsm IS
BEGIN
--state register process
state_reg:PROCESS
BEGIN
WAIT UNTIL clock'EVENT AND clock = '1';
present_state <= next_state;
END PROCESS;
--combinational logic feedback process
fb_logic:PROCESS(present_state,x)
BEGIN
CASE present_state IS
WHEN s0 =>
IF x = '0' THEN z <= '0'; next_state <= s0;
ELSE z <= '1'; next_state <= s2;
END IF;
WHEN s1 =>
IF x = '0' THEN z <= '0'; next_state <= s0;
ELSE z <= '0'; next_state <= s2;
END IF;
WHEN s2 =>
IF x = '0' THEN z <= '1'; next_state <= s2;
ELSE z <= '0'; next_state <= s3;
END IF;
WHEN s3 =>
IF x = '0' THEN z <= '0'; next_state <= s3;
ELSE z <= '1'; next_state <= s1;
END IF;
END CASE;
END PROCESS;
END behaviour;
-----------------------------------------------------------
--STIMULUS GENERATOR FOR FSM
ENTITY fsm_stim IS
END behavioural;
-----------------------------------------------
ENTITY fsm_bench IS
END fsm_bench;
ENTITY fsm2 IS
BEGIN
PROCESS
BEGIN
END CASE;
END PROCESS;
END using_wait;
-----------------------------------------------------------
library ieee;
use ieee.std_logic_1164.all;
entity stmch1 is
port(clk, in1, rst: in std_logic; out1: out std_logic);
end stmch1;
LIBRARY ieee;
USE ieee.Std_logic_1164.ALL;
ENTITY patdet IS
PORT(clock, serin, reset : IN Std_logic; match : OUT Std_logic);
END patdet;
ARCHITECTURE v1 OF patdet IS
TYPE state_type IS (s0, s1, s2, s3, s4, s5, s6, s7, s8);
SIGNAL pstate, nstate : state_type;
BEGIN
--state register
PROCESS
BEGIN
WAIT UNTIL rising_edge(clock);
IF reset = '1' THEN
pstate <= s0;
ELSE
pstate <= nstate;
END IF;
END PROCESS;
--generate output
match <= '1' WHEN pstate = s7 ELSE '0';
END v1;
LIBRARY ieee;
USE ieee.Std_logic_1164.ALL;
ENTITY prbsgen IS
GENERIC(length : Positive := 8; tap1 : Positive := 8; tap2 : Positive := 4);
PORT(clk, reset : IN Std_logic; prbs : OUT Std_logic);
END prbsgen;
ARCHITECTURE v3 OF prbsgen IS
BEGIN
END v3;
LIBRARY ieee;
USE ieee.Std_logic_1164.ALL;
ENTITY patdetbench IS
END patdetbench;
COMPONENT patdet
PORT(clock, serin, reset : IN Std_logic; match : OUT Std_logic);
END COMPONENT;
BEGIN
--clock generator
PROCESS
BEGIN
clock <= '0', '1' AFTER 50 ns;
WAIT FOR 100 ns;
END PROCESS;
END precomp;
Chess Clock
PACKAGE chesspack IS
TYPE elapsed_time IS
RECORD
hh : hours;
mm : minutes;
ss : seconds;
END RECORD;
END chesspack;
END chesspack;
USE WORK.chesspack.ALL;
ENTITY timer IS
--time_used must be inout port since signal assignment statement
--reads it's value to compute the new value of time_used.
PORT(enable,clear,one_sec : IN BIT; time_used : INOUT elapsed_time);
END timer;
BEGIN
END behaviour;
------------------------------------------------------------------
USE WORK.chesspack.ALL;
ENTITY chessclock IS
PORT(a,b,hold_time,reset_time : IN BIT;
time_a,time_b : INOUT elapsed_time);
END chessclock;
COMPONENT timer
PORT(enable,clear,one_sec : IN BIT; time_used : INOUT elapsed_time);
END COMPONENT;
BEGIN
--state register
state_reg:BLOCK
BEGIN
PROCESS(clock)
BEGIN
IF (clock'EVENT AND clock = '1' AND clock'LAST_VALUE = '0')
THEN present_state <= next_state;
END IF;
END PROCESS;
END BLOCK state_reg;
one_sec_clock:BLOCK
BEGIN
PROCESS --process to generate one second clock
BEGIN
one_sec <= TRANSPORT '1' AFTER 500 ms;
system_clock:BLOCK
BEGIN
PROCESS --process to generate 10Hz state machine clock
BEGIN
clock <= TRANSPORT '1' AFTER 50 ms;
clock <= TRANSPORT '0' AFTER 100 ms;
WAIT FOR 100 ms;
END PROCESS;
END BLOCK system_clock;
END structure;
PACKAGE rampac IS
END rampac;
PACKAGE adcpac IS
SUBTYPE analogue IS REAL RANGE -5.0 TO +5.0;
END adcpac;
USE WORK.rampac.ALL;
USE WORK.adcpac.ALL;
ENTITY adc16 IS
GENERIC(tconv : TIME := 10 us); --conversion time
PORT(vin : IN analogue; digout : OUT data16; --input and output
sc : IN BIT; busy : OUT BIT); --control
END adc16;
USE WORK.rampac.ALL;
USE WORK.adcpac.ALL;
ENTITY dac16 IS
PORT(vout : INOUT analogue; digin : IN data16; --input and output
en : IN BIT); --latches in data
END dac16;
USE WORK.rampac.ALL;
USE WORK.adcpac.ALL;
ENTITY digdel2 IS
PORT(clear : IN BIT; --clears address counter
offset : IN addr10; --delay control
sigin : IN analogue; --signal input
sigout : INOUT analogue); --signal output
END digdel2;
COMPONENT adc16
PORT(vin : IN analogue; digout : OUT data16;
sc : IN BIT; busy : OUT BIT);
END COMPONENT;
COMPONENT dac16
PORT(vout : INOUT analogue; digin : IN data16;
en : IN BIT);
END COMPONENT;
BEGIN
IF cs = '1' THEN
IF write = '1' THEN
ram_data(address) := ram_data_in;
END IF;
ram_data_out <= ram_data(address);
ELSE
ram_data_out <= z_val;
END IF;
END PROCESS;
END BLOCK ram;
END block_struct;
USE WORK.rampac.ALL;
USE WORK.adcpac.ALL;
ENTITY delay_bench IS
PORT(reset : IN BIT; delay : IN addr10);
END delay_bench;
COMPONENT sinegen
PORT(sinewave : OUT analogue);
END COMPONENT;
COMPONENT digdel2
PORT(clear : IN BIT; offset : IN addr10;
sigin : IN analogue; sigout : INOUT analogue);
END COMPONENT;
BEGIN
END;
PROCESS
BEGIN
digtemp := 0;
END PROCESS;
END behaviour;
ENTITY adcsc8 IS
PORT(vin : IN REAL RANGE 0.0 TO +5.0; --unipolar analogue input
digout : OUT BIT_VECTOR(7 DOWNTO 0); --digital output
clock, sc : IN BIT; busy : OUT BIT); --clock & control
END adcsc8;
PROCESS
BEGIN
END LOOP;
END PROCESS;
END behaviour;
ENTITY dev164 IS
PORT(a, b, nclr, clock : IN BIT;
q : BUFFER BIT_VECTOR(0 TO 7));
END dev164;
ENTITY dtff IS
GENERIC(initial : BIT := '1'); --initial value of q
PORT(d, clock : IN BIT; q : BUFFER BIT := initial);
END dtff;
END zero_delay;
COMPONENT dtff
GENERIC(initial : BIT := '1');
PORT(d, clock : IN BIT; q : BUFFER BIT := initial);
END COMPONENT;
BEGIN
reg_cells : FOR i IN 0 TO 7
GENERATE
reg_stage : dtff GENERIC MAP ('0') PORT MAP (datain(i) , clock, parout(i));
lsb_stage : IF i = 0 GENERATE
datain(i) <= parin(i) WHEN mode = "00" ELSE serinl WHEN mode = "10"
ELSE parout(i + 1) WHEN mode = "01" ELSE parout(i);
END GENERATE;
msb_stage : IF i = 7 GENERATE
datain(i) <= parin(i) WHEN mode = "00" ELSE parout(i - 1) WHEN mode =
"10"
ELSE serinr WHEN mode = "01" ELSE parout(i);
END GENERATE;
END GENERATE;
END structural;
library IEEE;
use IEEE.Std_logic_1164.all;
use IEEE.Std_logic_unsigned.all;
entity MUL8X8 is
port(A, B : in Std_logic_vector(7 downto 0);
PROD : out Std_logic_vector(15 downto 0));
end MUL8X8;
ENTITY addn IS
GENERIC(n : POSITIVE := 3); --no. of bits less one
PORT(addend, augend : IN BIT_VECTOR(0 TO n);
carry_in : IN BIT; carry_out, overflow : OUT BIT;
sum : OUT BIT_VECTOR(0 TO n));
END addn;
------------------------------------------------------------------------
-- Single-bit adder
------------------------------------------------------------------------
library IEEE;
use IEEE.std_logic_1164.all;
entity adder is
port (a : in std_logic;
b : in std_logic;
cin : in std_logic;
sum : out std_logic;
cout : out std_logic);
end adder;
------------------------------------------------------------------------
-- N-bit adder
-- The width of the adder is determined by generic N
------------------------------------------------------------------------
library IEEE;
use IEEE.std_logic_1164.all;
entity adderN is
generic(N : integer := 16);
port (a : in std_logic_vector(N downto 1);
b : in std_logic_vector(N downto 1);
cin : in std_logic;
sum : out std_logic_vector(N downto 1);
cout : out std_logic);
end adderN;
LIBRARY ieee;
USE ieee.Std_logic_1164.ALL;
USE ieee.Std_logic_unsigned.ALL;
ENTITY cntrnbit IS
GENERIC(n : Positive := 8);
PORT(clock, reset, enable : IN Std_logic;
count : OUT Std_logic_vector((n-1) DOWNTO 0));
END cntrnbit;
ARCHITECTURE v1 OF cntrnbit IS
SIGNAL count_int : Std_logic_vector((n-1) DOWNTO 0);
BEGIN
PROCESS
BEGIN
WAIT UNTIL rising_edge(clock);
IF reset = '1' THEN
count_int <= (OTHERS => '0');
ELSIF enable = '1' THEN
count_int <= count_int + 1;
ELSE
NULL;
END IF;
END PROCESS;
count <= count_int;
END v1;
library ieee;
use ieee.std_logic_1164.all;
end archmoore1;
library ieee;
use ieee.std_logic_1164.all;
end archmealy;
library ieee;
use ieee.std_logic_1164.all;
library ieee;
use ieee.std_logic_1164.all;
library ieee;
use ieee.std_logic_1164.all;
library ieee;
use ieee.std_logic_1164.all;
library ieee;
use ieee.std_logic_1164.all;
with s select
x <= a when "00",
b when "01",
c when "10",
d when "11",
(others => 'X') when others;
end archmux;
------------------------------------------------------------------------
-- package with component declarations
------------------------------------------------------------------------
library IEEE;
use IEEE.std_logic_1164.all;
package gates is
component andg
generic (tpd_hl : time := 1 ns;
tpd_lh : time := 1 ns);
port (in1, in2 : std_ulogic;
out1 : out std_ulogic);
end component;
component org
generic (tpd_hl : time := 1 ns;
tpd_lh : time := 1 ns);
port (in1, in2 : std_logic;
out1 : out std_logic);
end component;
component xorg
generic (tpd_hl : time := 1 ns;
tpd_lh : time := 1 ns);
port (in1, in2 : std_logic;
out1 : out std_logic);
end component;
end gates;
------------------------------------------------------------------------
-- or gate
------------------------------------------------------------------------
library IEEE;
use IEEE.std_logic_1164.all;
entity org is
generic (tpd_hl : time := 1 ns;
tpd_lh : time := 1 ns);
port (in1, in2 : std_logic;
out1 : out std_logic);
end org;
architecture only of org is
begin
p1: process(in1, in2)
variable val : std_logic;
begin
val := in1 or in2;
case val is
when '0' =>
out1 <= '0' after tpd_hl;
when '1' =>
out1 <= '1' after tpd_lh;
when others =>
out1 <= val;
end case;
end process;
end only;
------------------------------------------------------------------------
-- exclusive or gate
------------------------------------------------------------------------
library IEEE;
use IEEE.std_logic_1164.all;
entity xorg is
generic (tpd_hl : time := 1 ns;
tpd_lh : time := 1 ns);
port (in1, in2 : std_logic;
out1 : out std_logic);
architecture v1 of addrdec is
begin
entity priority is
port(I : in bit_vector(7 downto 0); --inputs to be prioritised
A : out bit_vector(2 downto 0); --encoded output
GS : out bit); --group signal output
end priority;
architecture v1 of priority is
begin
process(I)
begin
GS <= '1'; --set default outputs
A <= "000";
if I(7) = '1' then
A <= "111";
elsif I(6) = '1' then
A <= "110";
elsif I(5) = '1' then
A <= "101";
elsif I(4) = '1' then
A <= "100";
elsif I(3) = '1' then
A <= "011";
elsif I(2) = '1' then
A <= "010";
elsif I(1) = '1' then
A <= "001";
elsif I(0) = '1' then
A <= "000";
else
GS <= '0';
end if;
end process;
end v1;
A jointly validated MSc course taught over the internet; a programme supported by EPSRC under the Integrated Graduate Development Scheme (IGDS).
Text & images © 1999 Bolton Institute and Northumbria University unless otherwise stated.
website www.ami.ac.uk
A website devoted to the provision of on-line computer-based distance learning via the internet.
A dedicated installation of web servers and powerful "number-crunching" computers at Bolton Institute provides a reliable
service to distance learning students, including remote access to computer aided design (CAD) software. More
details.
The CRAL video describes how the Centre was established and funded by the DfEE under the Centres of Excellence
initiative. It lasts seven minutes and was produced entirely in-house.
CRAL supports the business community too; for details please follow this link to our commercial web design and
development service.