The VHDL Source Code for the Countdown Clock
You can find the complete VHDL version of the source code for the countdown clock
project on this page. The code has been tested and is running on my project board. The
performance of the countdown clock with the VHDL code is of course identical to the AHDL
version. I have simply replaced the AHDL code with equivalent VHDL code, taking into
account the style of VHDL code. The block diagram for the VHDL code is the same as the
hierarchy diagram given for the AHDL code. There are numerous small differences between
VHDL and AHDL and VHDL has more ways of doing the same thing but after allowing for the
idiosyncrasies of the two languages they give much the same results.
Since VHDL is an industry standard, it has a high degree of portability between
different manufacturers. However, it is still necessary to instantiate some of the
components of a particular manufacturer. In the present project it is necessary to
instantiate a number of lcell's and the open drain outputs required for the keyboard
column driver circuits. The lcell's are necessary to minimise the resources required for
the project and to enable the circuitry to fit into the selected device. Doing this more
than halves the resources needed to fit the project. In the case of VHDL this requires
increasing the number of signals that are defined for the project, since an input and an
output is required for each instantiation. The exercise of inserting lcell's calls for
some experimentation, although there is a sensible way of doing this, a task that is
somewhat greater for VHDL than it is for AHDL, since component definitions are directly
available in the AHDL code but have to be instantiated in the VHDL code. The instantiated
lcell's have to be added and possibly removed if found not to be effective in reducing
resource usage, a process that requires some care and can be quite tedious. This has
increased the amount of code for the VHDL source. I have included the component
declaration package code at the end of the code listings.
Added note 26 June 2008: VHDL has a procedure for dealing with open
drain outputs, which I was not aware of at the time that I posted this code. You should
look this up and replace it in the code on this page. Also if you are using FPGA,s or more
recent programmable logic devices you may not need to use the lcells since these devices
have considerably more resources. I will leave the code as it is.
Top
level VHDL code for the Countdown Clock
LIBRARY ieee;
USE ieee.STD_LOGIC_1164.all;
USE ieee.STD_LOGIC_UNSIGNED.all;
USE work.COUNTDOWN_PACKAGE.all;
LIBRARY altera;
USE altera.maxplus2.all;
-- Title "Count Down clock exercise";
-- Written by: D. N. Warren-Smith
-- Updated: 14 February 2001
--
-- The count down clock will count down minutes and seconds.
-- When zero is reached the count down clock will beep and count upwards
-- if dipswitch 1 is not set.
-- If dipswitch 1 is set the countdown will begin again at the value in
-- the input shift register.
-- The input shift register can be reentered whilst a countdown is in
-- progress.
--
-- Key Control Functions
-- Plus key = Load and run new Start Value
-- Minus key = Start/Stop/Pause
-- Clear key = Toggle display
-- "D" keyboard = Switch to Time display
-- "E" keyboard = Backspace
-- "F" keyboard = Clear input display
-- Restart on zero with Dip switch 1 ON
-- Buzzer disabled with Dip switch 8 ON
ENTITY cdclock IS
PORT (
clock, resetn : IN STD_LOGIC; -- clock = 1024 Hz from 4060B
plus_keyn : IN STD_LOGIC; -- transfer data to counters
minus_keyn : IN STD_LOGIC; -- run / pause key
clear_keyn : IN STD_LOGIC; -- toggle display
Hz512 : IN STD_LOGIC; -- display multiplexer clock
row : IN STD_LOGIC_VECTOR (3 downto 0); -- Sense rows
dip : IN STD_LOGIC_VECTOR (4 downto 1); -- dip sws 1 to 4
dip8 : IN STD_LOGIC; -- dip switch 8
sparein : IN STD_LOGIC; -- Spare input not used
colout : OUT STD_LOGIC_VECTOR (3 downto 0); -- drive columns low
dr : OUT STD_LOGIC_VECTOR (3 downto 0); -- transistor drivers
s : OUT STD_LOGIC_VECTOR (6 downto 0); -- display 7 segments
dp : OUT STD_LOGIC_VECTOR (4 downto 1); -- decimal point LEDs
buz : OUT STD_LOGIC; -- buzzer
led : OUT STD_LOGIC; -- LED indicator
strobe_test : OUT STD_LOGIC); -- Temp for test
END cdclock;
ARCHITECTURE countdown OF cdclock IS
SIGNAL start : STD_LOGIC;
SIGNAL set : STD_LOGIC; -- set counters from input register
SIGNAL strobe : STD_LOGIC; -- clean pulse from keyboard
SIGNAL clear : STD_LOGIC; -- clear input registers
SIGNAL toggle : STD_LOGIC; -- toggle display between input and count
SIGNAL usec : STD_LOGIC_VECTOR (3 DOWNTO 0); -- units seconds
SIGNAL tsec : STD_LOGIC_VECTOR (2 DOWNTO 0); -- tens seconds
SIGNAL umin : STD_LOGIC_VECTOR (3 DOWNTO 0); -- units minutes
SIGNAL tmin : STD_LOGIC_VECTOR (2 DOWNTO 0); -- tens minutes
SIGNAL carin : STD_LOGIC; -- carry in
SIGNAL csout : STD_LOGIC;
SIGNAL cout : STD_LOGIC;
SIGNAL restart : STD_LOGIC; -- Restart on zero
SIGNAL restart_l : STD_LOGIC; -- Restart with lcell
SIGNAL dir : STD_LOGIC; -- count direction, 0 = down, 1 = up
SIGNAL zerom1 : STD_LOGIC; -- zero minus 1
SIGNAL zerom1_l : STD_LOGIC; -- lcell - zero minus 1
SIGNAL zero : STD_LOGIC; -- counted down to zero
SIGNAL zero_l : STD_LOGIC; -- lcell - counted down to zero
SIGNAL zerop1 : STD_LOGIC; -- zero plus 1
SIGNAL alarmne0 : STD_LOGIC; -- alarm not equal to 0
SIGNAL alarm : STD_LOGIC_VECTOR (1 downto 0); -- indicate zero reached
SIGNAL shift : STD_LOGIC_VECTOR (15 downto 0); -- input shift reg for display
SIGNAL time : STD_LOGIC_VECTOR (15 downto 0); -- count down time display
SIGNAL prectr : STD_LOGIC_VECTOR (9 downto 0); -- prescaler counter
SIGNAL col : STD_LOGIC_VECTOR (3 downto 0); -- OPNDRN col. drivers open drain
SIGNAL pre : STD_LOGIC; -- prescaler counter at zero
SIGNAL pre_l : STD_LOGIC; -- prescalar lcell
SIGNAL dispreg : STD_LOGIC; -- determine which display required
SIGNAL startreg : STD_LOGIC; -- set when counting down started
SIGNAL t_min0 : STD_LOGIC; -- tens minutes at zero
SIGNAL u_min0 : STD_LOGIC; -- units minutes at zero
SIGNAL t_sec0 : STD_LOGIC; -- tens seconds at zero
SIGNAL u_sec0 : STD_LOGIC; -- units seconds at zero
SIGNAL u_sec1 : STD_LOGIC; -- units seconds at 1
BEGIN
-- Debounce the start/stop, set and toggle keys
deb_set : debounce PORT MAP(clock, plus_keyn, set); -- set countdown
deb_start : debounce PORT MAP(clock, minus_keyn, start); -- start/pause
deb_toggle : debounce PORT MAP(clock, clear_keyn, toggle); -- toggle display
-- Prescaler counter
PROCESS (clock, resetn)
BEGIN
IF (resetn = '0') OR ((NOT set AND startreg) = '0')
THEN prectr <= "0000000000"; -- asynchronous clear
ELSIF (clock'EVENT AND clock = '1') -- prescaler counter
THEN prectr <= prectr + 1;
END IF;
END PROCESS;
pre <= '1' WHEN (prectr = "1111111111") ELSE '0';
pr : lcell PORT MAP(pre, pre_l); -- buffer pre with an lcell
-- Connect up the hex keypad
pad : Hexkbd PORT MAP(clock, resetn, strobe, row, col, shift);
strobe_test <= strobe;
co1: FOR i IN 0 TO 3 GENERATE -- keyboard column drivers are open drain
co2 : opndrn PORT MAP(col(i), colout(i));
END GENERATE;
-- Start the countdown
PROCESS (clock)
BEGIN -- counting when startreg is high
IF resetn = '0' THEN startreg <= '0'; -- asynchronous reset
ELSIF (clock'EVENT AND clock = '1') THEN -- Toggle start/pause
IF start = '1' THEN startreg <= startreg XOR '1'; END IF;
END IF;
END PROCESS;
-- restart on zero or set option
restart <= set OR (zerop1 AND NOT dip(1));
rest : lcell PORT MAP(restart, restart_l); -- buffer restart with an lcell
-- Count down circuits
carin <= (startreg AND pre_l);
Divider1 : Div60 PORT MAP(clock, resetn, carin, restart_l, dir,
shift(3 DOWNTO 0), shift(6 DOWNTO 4),
csout, usec(3 DOWNTO 0), tsec(2 DOWNTO 0));
Divider2 : Div60 PORT MAP(clock, resetn, csout, restart_l, dir,
shift(11 DOWNTO 8), shift(14 DOWNTO 12), cout,
umin(3 DOWNTO 0), tmin(2 DOWNTO 0));
time <= ('0' & tmin(2 DOWNTO 0) & umin(3 DOWNTO 0) & '0' &
tsec(2 DOWNTO 0) & usec(3 DOWNTO 0)); -- concatinate time
-- Count down at zero
t_min0 <= '1' WHEN (tmin = "000") ELSE '0';
u_min0 <= '1' WHEN (umin = "0000") ELSE '0';
t_sec0 <= '1' WHEN (tsec = "000") ELSE '0';
u_sec0 <= '1' WHEN (usec = "0000") ELSE '0';
u_sec1 <= '1' WHEN (usec = "0001") ELSE '0';
zerom1 <= (t_min0 AND u_min0 AND t_sec0 AND u_sec1 AND dir); -- zero minus 1
ze1 : lcell PORT MAP(zerom1, zerom1_l); -- buffered with an lcell
zero <= (t_min0 AND u_min0 AND t_sec0 AND u_sec0); -- at zero
ze2 : lcell PORT MAP(zero, zero_l); -- buffered with an lcell
PROCESS (clock, resetn) -- zerop1 = pulse at zero plus 1
BEGIN
IF (resetn = '0') THEN zerop1 <= '0'; -- asynchronous rest
ELSIF (clock'EVENT AND clock = '1') -- zero indicated
THEN zerop1 <= zero_l AND pre_l; -- 1 second delay
END IF;
END PROCESS;
-- Set the count direction, 0 = count up, 1 = count down
PROCESS (clock, resetn)
BEGIN
IF (clock'EVENT AND clock = '1') THEN -- zero indicated
IF (set = '1') THEN dir <= '1'; -- count down
ELSIF (zero_l AND dip(1)) = '1' THEN dir <= '0'; -- count up
END IF;
END IF;
END PROCESS;
-- Determine the display required
-- dispreg low = Display Time, dispreg high = Display input register
PROCESS (clock)
BEGIN
IF (clock'EVENT AND clock = '1') THEN --
IF toggle = '1' THEN dispreg <= dispreg XOR '1';
ELSIF (start OR set) = '1' THEN dispreg <= '0';
ELSIF strobe = '1' THEN dispreg <= '1';
END IF;
END IF;
END PROCESS;
-- Setup the display circuits
disp : display PORT MAP(hz512, dispreg, time, shift, s, dr);
-- Indicate that zero has been reached
PROCESS (clock)
BEGIN
IF resetn = '0' THEN alarm <= "00"; -- async clear
ELSIF (clock'EVENT AND clock = '1') THEN
IF (set = '1') THEN alarm <= "00"; -- synch clear
ELSIF (zerom1_l AND pre_l) = '1' THEN alarm <= "01"; -- start alarm
ELSIF (alarm /= "00") AND (pre_l = '1') THEN alarm <= alarm + 1;
END IF; -- alarm ends when alarm count returns to zero
END IF;
END PROCESS;
-- Activate buzzer when zero reached. Alarm active when alarm ctr ne to 0
alarmne0 <= '1' WHEN (alarm /= "00") ELSE '0';
buz <= startreg AND alarmne0 AND dip8 AND NOT prectr(6) AND NOT prectr(9);
-- Connect unused inputs and outputs for compatibility
led <= startreg;
dp(1) <= NOT dispreg;
dp(2) <= dispreg;
dp(3) <= NOT (dip(2) AND dip(3) AND dip(4) AND sparein);
dp(4) <= NOT (dip(2) AND dip(3) AND dip(4) AND sparein);
END countdown;
Keypad
encoder circuit
LIBRARY ieee;
USE ieee.STD_LOGIC_1164.all;
USE ieee.STD_LOGIC_UNSIGNED.all;
USE work.COUNTDOWN_PACKAGE.all;
LIBRARY altera;
USE altera.maxplus2.all;
-- Title "Keypad encoder circuit"
-- Prepared by: D.N. Warren-Smith
-- Updated: 14 February 2001
ENTITY hexkbd IS
PORT (
clk : IN STD_LOGIC; -- Clock source and
resetn : IN STD_LOGIC; -- Reset on global inputs
strobe : BUFFER STD_LOGIC; -- key pressed
row : IN STD_LOGIC_VECTOR (3 DOWNTO 0); -- Sense keypad rows
col : OUT STD_LOGIC_VECTOR (3 DOWNTO 0); -- Drive columns
shift : OUT STD_LOGIC_VECTOR (15 DOWNTO 0)); -- Shift reg output
END hexkbd;
ARCHITECTURE keys OF hexkbd IS
SIGNAL key_pressed : STD_LOGIC; -- High when a key pressed
SIGNAL NKP : STD_LOGIC;
SIGNAL sh9 : STD_LOGIC; -- conditional signal for shift logic
SIGNAL sh9_l : STD_LOGIC; -- conditional signal for shift logic
SIGNAL shF : STD_LOGIC; -- conditional signal for shift logic
SIGNAL shF_l : STD_LOGIC; -- conditional signal for shift logic
SIGNAL shE : STD_LOGIC; -- conditional signal for shift logic
SIGNAL shE_l : STD_LOGIC; -- conditional signal for shift logic
SIGNAL mat : STD_LOGIC_VECTOR (3 DOWNTO 0); -- key conversion matrix
SIGNAL d : STD_LOGIC_VECTOR (3 DOWNTO 0); -- Control counter
SIGNAL inp0 : STD_LOGIC_VECTOR (3 DOWNTO 0); -- First stage of shift register
SIGNAL inp1 : STD_LOGIC_VECTOR (3 DOWNTO 0); -- Second stage of shift register
SIGNAL inp2 : STD_LOGIC_VECTOR (3 DOWNTO 0); -- Third stage of shift register
SIGNAL inp3 : STD_LOGIC_VECTOR (3 DOWNTO 0); -- Fourth stage of shift register
BEGIN
-- Scan the keyboard until a key is pressed
PROCESS (clk, key_pressed)
BEGIN
IF (resetn = '0') THEN d <= "0000"; -- asynchronous reset
ELSIF (clk'EVENT AND clk = '1') THEN
IF (key_pressed = '0') THEN d <= d + 1; END IF;
END IF; -- Counter stops counting when a key is pressed
END PROCESS;
-- Column drivers, active low
col(0) <= '0' WHEN d(3 DOWNTO 2) = "00" ELSE '1';
col(1) <= '0' WHEN d(3 DOWNTO 2) = "01" ELSE '1';
col(2) <= '0' WHEN d(3 DOWNTO 2) = "10" ELSE '1';
col(3) <= '0' WHEN d(3 DOWNTO 2) = "11" ELSE '1';
-- Sense keyboard rows with a multiplexer
WITH d(1 DOWNTO 0) SELECT
key_pressed <= NOT row(3) WHEN "11",
NOT row(2) WHEN "10",
NOT row(1) WHEN "01",
NOT row(0) WHEN OTHERS;
NKP <= NOT key_pressed;
-- Generate strobe when key press has settled
st : debounce PORT MAP(clk, NKP, strobe);
-- The key scan matrix
PROCESS (D)
BEGIN
CASE D IS --
WHEN "0000" => mat <= "0001";
WHEN "0001" => mat <= "0100";
WHEN "0010" => mat <= "0111";
WHEN "0011" => mat <= "1111";
WHEN "0100" => mat <= "0010";
WHEN "0101" => mat <= "0101";
WHEN "0110" => mat <= "1000";
WHEN "0111" => mat <= "0000";
WHEN "1000" => mat <= "0011";
WHEN "1001" => mat <= "0110";
WHEN "1010" => mat <= "1001";
WHEN "1011" => mat <= "1110";
WHEN "1100" => mat <= "1010";
WHEN "1101" => mat <= "1011";
WHEN "1110" => mat <= "1100";
WHEN "1111" => mat <= "1101";
WHEN OTHERS => mat <= "----";
END CASE;
END PROCESS;
-- The data shift register circuit
-- F clears input register, E backspaces input register
-- any other key A to D not input here
-- instantiate conditional signals for shift register with lcell's
sh9 <= '1' WHEN (strobe = '1') AND (mat <= "1001") ELSE '0';
sh1 : lcell PORT MAP(sh9, sh9_l);
shF <= '1' WHEN ((strobe = '1') AND (mat = "1111")) ELSE '0';
sh2 : lcell PORT MAP(shF, shF_l);
shE <= '1' WHEN (strobe = '1') AND (mat = "1110") ELSE '0';
sh3 : lcell PORT MAP(shE, shE_l);
PROCESS (clk)
BEGIN
IF resetn = '0' -- asynchronous clear
THEN inp0 <= "0000"; inp1 <= "0000"; inp2 <= "0000"; inp3 <= "0000";
ELSIF (clk'EVENT AND clk = '1') THEN
IF shF_l = '1' -- clear shift register
THEN inp0 <= "0000"; inp1 <= "0000"; inp2 <= "0000"; inp3 <= "0000";
ELSIF shE_l = '1' -- shift right shift register
THEN inp0 <= inp1; inp1 <= inp2; inp2 <= inp3; inp3 <= "0000";
ELSIF sh9_l = '1' -- left shift mat into shift register
THEN inp0 <= mat; inp1 <= inp0; inp2 <= inp1; inp3 <= inp2;
END IF;
END IF;
END PROCESS;
-- Combine shift register into one statement
shift <= (inp3 & inp2 & inp1 & inp0);
END;
Divide
by 60 circuit
LIBRARY ieee;
USE ieee.STD_LOGIC_1164.all;
USE ieee.STD_LOGIC_UNSIGNED.all;
LIBRARY altera;
USE altera.maxplus2.all;
-- TITLE "Divide by 60 counter.";
-- File: div60.vhd
-- Date: 14 FEB 2001
-- Prepared by: David Warren-Smith
-- This version of DIV60 does "Parallel set"
ENTITY DIV60 IS
PORT (
clk, resetn,
cin : IN STD_LOGIC;
set : IN STD_LOGIC; -- run = (set = 0), set = (set = 1)
dir : IN STD_LOGIC; -- 0 = count up, 1 = count down
uin : IN STD_LOGIC_VECTOR (3 DOWNTO 0); -- units to load
tin : IN STD_LOGIC_VECTOR (2 DOWNTO 0); -- tens to load
cout : OUT STD_LOGIC;
uq : OUT STD_LOGIC_VECTOR (3 DOWNTO 0); -- Units output
tq : OUT STD_LOGIC_VECTOR (2 DOWNTO 0)); -- Tens output
END DIV60;
ARCHITECTURE DIVIDER OF DIV60 IS
SIGNAL car : STD_LOGIC;
SIGNAL u0 : STD_LOGIC; -- conditional signals for counters
SIGNAL t0 : STD_LOGIC;
SIGNAL u9 : STD_LOGIC;
SIGNAL t5 : STD_LOGIC;
SIGNAL u : STD_LOGIC_VECTOR (3 DOWNTO 0); -- units counter
SIGNAL t : STD_LOGIC_VECTOR (2 DOWNTO 0); -- tens counter
BEGIN
-- define conditionals for counters
car <= cin AND NOT set;
u0 <= '1' WHEN (u = "0000") AND (car AND dir) = '1' ELSE '0';
u9 <= '1' WHEN (u = "1001") AND (car AND NOT dir) = '1' ELSE '0';
t0 <= '1' WHEN (t = "000") ELSE '0';
t5 <= '1' WHEN (t = "101") ELSE '0';
PROCESS (clk)
BEGIN
IF resetn = '0' THEN u <= "0000"; -- asynch reset
ELSIF (clk'EVENT AND clk = '1') THEN -- Units counter
IF set = '1' THEN u <= uin; -- set
ELSIF u0 = '1' THEN u <= "1001"; -- loadu
ELSIF (car AND dir) = '1' THEN u <= u - 1; -- decu
ELSIF u9 = '1' THEN u <= "0000"; -- clru
ELSIF (car AND NOT dir) = '1' THEN u <= u + 1; -- incu
END IF;
END IF;
IF resetn = '0' THEN t <= "000"; -- asynch reset
ELSIF (clk'EVENT AND clk = '1') THEN -- Tens counter
IF set = '1' THEN t <= tin; -- set
ELSIF (t0 AND u0) = '1' THEN t <= "101"; -- loadt
ELSIF u0 = '1' THEN t <= t - 1; -- dect
ELSIF (t5 AND u9) = '1' THEN t <= "000"; -- clrt
ELSIF u9 = '1' THEN t <= t + 1; -- inct
END IF;
END IF;
cout <= (u0 AND t0 AND cin AND NOT set AND dir) OR -- Carry out circuit
(u9 AND t5 AND cin AND NOT set AND NOT dir);
uq <= u; -- Connect outputs
tq <= t;
END PROCESS;
END DIVIDER;
Key
debounce circuit
LIBRARY ieee;
USE ieee.STD_LOGIC_1164.all;
USE ieee.STD_LOGIC_UNSIGNED.all;
-- Title "Key debounce circuit";
-- Prepared by: D. N. Warren-Smith
-- Updated: 7 February 2001
ENTITY DEBOUNCE IS
PORT (
Clk : IN STD_LOGIC;
Key : IN STD_LOGIC; -- active low input
pulse : OUT STD_LOGIC);
END DEBOUNCE;
ARCHITECTURE clean_pulse OF DEBOUNCE IS
SIGNAL cnt : STD_LOGIC_VECTOR (1 DOWNTO 0);
BEGIN
PROCESS (Clk)
BEGIN
IF Key = '1' THEN
cnt <= "00";
ELSIF (clk'EVENT AND Clk = '1') THEN
IF (cnt /= "11") THEN cnt <= cnt + 1; END IF;
END IF;
IF (cnt = "10") AND (Key = '0') THEN pulse <= '1'; ELSE pulse <= '0'; END IF;
END PROCESS;
END clean_pulse;
Display
multiplexer circuits
LIBRARY ieee;
USE ieee.STD_LOGIC_1164.all;
USE ieee.STD_LOGIC_UNSIGNED.all;
USE work.COUNTDOWN_PACKAGE.all;
LIBRARY altera;
USE altera.maxplus2.all;
-- Title " Multiplexer circuits"
-- Prepared by: D.N. Warren-Smith
-- File: DISPLAY.TDF
-- Updated: 7 February 2001
ENTITY DISPLAY IS
PORT (
HZ : IN STD_LOGIC;
dispreg : IN STD_LOGIC; -- Display register, 0=A, 1=B
A : IN STD_LOGIC_VECTOR (15 DOWNTO 0); -- Register A
B : IN STD_LOGIC_VECTOR (15 DOWNTO 0); -- Register B
seg : OUT STD_LOGIC_VECTOR (6 DOWNTO 0); -- 7-segment output
driv : OUT STD_LOGIC_VECTOR (3 DOWNTO 0)); -- drivers for multip/r tr/s
END DISPLAY;
ARCHITECTURE visual OF DISPLAY IS
SIGNAL mul : STD_LOGIC_VECTOR (1 DOWNTO 0); -- Multiplexer clock source
SIGNAL mx : STD_LOGIC_VECTOR (15 DOWNTO 0); -- 1st level multiplexer outputs
SIGNAL d7 : STD_LOGIC_VECTOR (3 DOWNTO 0); -- 2nd level multiplexer outputs
SIGNAL dl : STD_LOGIC_VECTOR (3 DOWNTO 0); -- 2nd level lcell outputs
BEGIN
PROCESS (HZ) -- Multiplexer clock source
BEGIN
IF (HZ'EVENT AND HZ = '1') THEN mul <= mul + 1; END IF;
END PROCESS;
-- First level Multiplexer combines A and B register inputs
mx <= A WHEN (dispreg = '0') ELSE B;
-- Second level Multiplexers combine 4 digits for display
d7 <= mx(3 DOWNTO 0) WHEN mul = "00" ELSE
mx(7 DOWNTO 4) WHEN mul = "01" ELSE
mx(11 DOWNTO 8) WHEN mul = "10" ELSE
mx(15 DOWNTO 12);
LCL : FOR i IN 0 TO 3 GENERATE
LC : lcell PORT MAP(d7(i), dl(i)); -- instantiate 4 LCELLs
END GENERATE;
SG : SEG7 PORT MAP(dl, seg); -- convert to 7-segment format
-- Decode multiplexer driver counter for common anode display tr. Drivers
driv <= "1110" WHEN mul = "00" ELSE -- Active low outputs
"1101" WHEN mul = "01" ELSE
"1011" WHEN mul = "10" ELSE
"0111";
END visual;
7-segment
display driver circuit
LIBRARY ieee;
USE ieee.std_logic_1164.all;
-- Title "7 segment display driver circuit";
-- File: seg7.vhd
ENTITY seg7 IS
PORT (D : IN STD_LOGIC_VECTOR (3 DOWNTO 0); -- BCD input
S : OUT STD_LOGIC_VECTOR (6 DOWNTO 0)); -- 7 segment outputs
END seg7;
ARCHITECTURE display OF SEG7 IS
BEGIN
s <= "1000000" WHEN d = "0000" ELSE -- H"40"
"1111001" WHEN d = "0001" ELSE -- H"79"
"0100100" WHEN d = "0010" ELSE -- H"24"
"0110000" WHEN d = "0011" ELSE -- H"30"
"0011001" WHEN d = "0100" ELSE -- H"19"
"0010010" WHEN d = "0101" ELSE -- H"12"
"0000010" WHEN d = "0110" ELSE -- H"02"
"1111000" WHEN d = "0111" ELSE -- H"78"
"0000000" WHEN d = "1000" ELSE -- H"00"
"0010000" WHEN d = "1001" ELSE -- H"10"
"0001000" WHEN d = "1010" ELSE -- H"08"
"0000011" WHEN d = "1011" ELSE -- H"03"
"1000110" WHEN d = "1100" ELSE -- H"46"
"0100001" WHEN d = "1101" ELSE -- H"21"
"0000110" WHEN d = "1110" ELSE -- H"06"
"0001110"; -- H"0E"
END display;
Countdown_Package - Component declarations
LIBRARY ieee;
USE ieee.STD_LOGIC_1164.all;
-- Subcircuit component declarations
-- Prepared by: D.N. Warren-Smith
-- Updated: 7 February 2001
PACKAGE COUNTDOWN_PACKAGE IS
COMPONENT debounce -- key debounce circuit
PORT ( clk, key : IN STD_LOGIC;
pulse : OUT STD_LOGIC);
END COMPONENT;
COMPONENT DIV60 -- divide by 60 with parallel load
PORT ( clk, resetn, -- clock and reset
cin, -- carry in
set, -- run = (set = '0'), set = (set = '1')
dir : IN STD_LOGIC; -- '0' = count up, '1' = count down
uin : IN STD_LOGIC_VECTOR (3 DOWNTO 0); -- units to load
tin : IN STD_LOGIC_VECTOR (2 DOWNTO 0); -- tens to load
cout : OUT STD_LOGIC;
uq : OUT STD_LOGIC_VECTOR (3 DOWNTO 0); -- units output
tq : OUT STD_LOGIC_VECTOR (2 DOWNTO 0)); -- tens output
END COMPONENT;
COMPONENT HEXKBD -- Keyboard input circuit with shift input register
PORT ( clk, -- clock
resetn : IN STD_LOGIC; -- reset
strobe : BUFFER STD_LOGIC; -- key pressed
row : IN STD_LOGIC_VECTOR (3 DOWNTO 0); -- Sense keypad rows
col : OUT STD_LOGIC_VECTOR (3 DOWNTO 0); -- Drive columns
shift : OUT STD_LOGIC_VECTOR (15 DOWNTO 0)); -- Shift reg output
END COMPONENT;
COMPONENT DISPLAY
PORT (
HZ : IN STD_LOGIC;
dispreg : IN STD_LOGIC; -- Display register, 0=A, 1=B
A : IN STD_LOGIC_VECTOR (15 DOWNTO 0); -- Register A
B : IN STD_LOGIC_VECTOR (15 DOWNTO 0); -- Register B
seg : OUT STD_LOGIC_VECTOR (6 DOWNTO 0); -- 7-segment output
driv : OUT STD_LOGIC_VECTOR (3 DOWNTO 0)); -- drivers for multip/r transistors
END COMPONENT;
COMPONENT seg7 -- 7 segment display conversion matrix
PORT (D : IN STD_LOGIC_VECTOR (3 DOWNTO 0); -- BCD input
S : OUT STD_LOGIC_VECTOR (6 DOWNTO 0)); -- 7 segment outputs
END COMPONENT;
END COUNTDOWN_PACKAGE;
End of VHDL code
Return to AHDL Source code OR
Navigation menu at the top of the page OR Return to the Project
Board page:
Copyright D.N. Warren-Smith, MSc. Digital Logic Systems
Last
edited: 26 June, 2008
|