Free Online Training Events
Free Technical Resources
The following examples of VHDL coding may be downloaded for use by readers of the Doulos VHDL Golden Reference Guide. You may freely use them in your projects subject to the Apache 2.0 License both privately and commercially. Please do not publish or re-distribute to others except by recommending they get a copy of our VHDL Golden Reference Guide. If you wish to use some fragment in a presentation or article you are writing, please request permission from Doulos.
Click here to download the examples below as a zip file, or use the links below to jump to a particular example.
Click on the links under each section to run prepared examples in a live simulation environment using EDA Playground.
Click here to use EDA Playground to run your own sample code.
Try out an example using this feature in EDA Playground
type NewName is access DataType; type IncompleteTypeName; type Item; -- Incomplete type declaration type Link is access Item; type Item is record Data: STD_LOGIC_VECTOR(7 downto 0); NextItem: Link; end record; variable StartOfList, Ptr: Link; -- Add item to start of list Ptr := new Item; -- Allocate storage Ptr.Data := "01010101"; Ptr.NextItem := StartOfList; -- Link item into list StartOfList := Ptr; -- Delete entire list while StartOfList /= null loop Ptr := StartOfList.NextItem; DEALLOCATE(StartOfList); StartOfList := Ptr; end loop;
Try out an example using this feature in EDA Playground
(1, 2, 3, 4) -- Positional association (A => 1, B => 2, C => 3, D => 4) -- Named association (1, 2, D => 4, C => 3) -- Mixed positional/named (1, 2, others => 4) ('0', '1', '0', '1') (others => 'Z') (A, B, C) := D; -- Target in the form of an aggregate (A, B, C) := T'("001"); -- Qualified expression T'(others => '0') -- Qualified expression (others => T'(others => '0'))
VHDL 2008 Examples
(ag1(3 downto 0), ag2(3 downto 0), ag1(7 downto 4)) ('0', '0', '0', '0', ag1(3 downto 0), ag2) ("1100", ag7(0 to 7), ag2) (ag1, ag2) <= STD_LOGIC_VECTOR'(ag3(7 downto 0), "1100"); (ag1, ag2) <= STD_LOGIC_VECTOR'(16X"F00F");
Try out an example using this feature in EDA Playground
function F (A, B: STD_LOGIC_VECTOR) return BOOLEAN is alias P1: STD_LOGIC_VECTOR(1 to A'LENGTH) is A; alias P2: STD_LOGIC_VECTOR(1 to B'LENGTH) is B; -- Alias is used to create 2 local vectors with the same range begin for I in P1'RANGE loop if P1(I) = P2(I) then --... alias ">" is F[STD_LOGIC_VECTOR, STD_LOGIC_VECTOR return BOOLEAN];
VHDL 2008 Example
alias sig1 is <<signal .testbench.comp1.i1 : STD_LOGIC>>;
Try out an example using this feature in EDA Playground
library IEEE; use IEEE.STD_LOGIC_1164.all; architecture BENCH of TEST_MUX4 is subtype V2 is STD_LOGIC_VECTOR(1 downto 0); -- Component declaration... component MUX4 port (SEL, A, B, C, D: in V2; F : out V2); end component; -- Internal signal... signal SEL, A, B, C, D, F: V2; begin P: process begin SEL <= "00"; wait for 10 NS; SEL <= "01"; wait for 10 NS, SEL <= "10"; wait for 10 NS, SEL <= "11"; wait for 10 NS; wait; end process P; -- Concurrent assignments... A <= "00"; B <= "01"; C <= "10"; D <= "11"; -- Component instantiation... M: MUX4 port map (SEL, A, B, C, D, F); end architecture BENCH;
Try out an example using this feature in EDA Playground
subtype Word is UNSIGNED(15 downto 0); type Mem is array (0 to 2**12-1) of Word; variable Memory: Mem := (others => Word'(others=>'U')); --... if MemoryRead then Data <= Memory(TO_INTEGER(Address)); elsif MemoryWrite then Memory(TO_INTEGER(Address)) := Data; end if;
VHDL 2008 Examples
type myMem is array(positive range<>) of STD_LOGIC_VECTOR; signal mem : myMem(1 to 1024)(7 downto 0); subtype mem2_t is myMem(1 to 512)(15 downto 0); signal mem3 : mem2_t;
Try out an example using this feature in EDA Playground
assert not (Reset = '0' and Set = '0') report "R-S conflict" severity Failure; assert Outputs = ExpectedOutputs report "Outputs differ from expected response"; report "value is " & to_string(expected_val); -- VHDL 2008
attribute Pin_number: Positive; attribute Pin_number of Clk: signal is 1; attribute Enum_encoding: String; attribute Enum_encoding of State: type is "11 00 01 10";
Try out an example using this feature in EDA Playground
type T is (A, B, C, D, E); subtype S is T range D downto B; S'LEFT = D S'RIGHT = B S'LOW = B S'HIGH = D S'BASE'LEFT = A T'ASCENDING = TRUE S'ASCENDING = FALSE T'IMAGE(A) = "a" T'VALUE("E") = E T'POS(A) = 0 S'POS(B) = 1 T'VAL(4) = E S'SUCC(B) = C S'PRED(C) = B S'LEFTOF(B) = C S'RIGHTOF(C) = B signal A: STD_LOGIC_VECTOR(7 downto 0); A'LEFT = 7 A'RIGHT = 0 A'LOW = 0 A'HIGH = 7 A'RANGE = 7 downto 0 A'REVERSE_RANGE = 0 to 7 A'LENGTH = 8 A'ASCENDING = FALSE
VHDL 2008 Examples
type myMem is array(positive range<>) of STD_LOGIC_VECTOR; subtype mem2_t is myMem(1 to 512)(15 downto 0); signal mem3: mem2_t; signal mem4 : mem3'subtype; -- returns mem2_t
Try out an example using this feature in EDA Playground
signal P, Q, R: STD_LOGIC; --... Logic: block port (A, B: in STD_LOGIC; F : out STD_LOGIC); port map (A => P, B => Q, F => R); begin F <= A nand B; end block Logic; Sync: block (Rising_edge(Clock)) begin Q <= guarded D; -- This assignment occurs on the clock edge QB <= not Q; -- This assignment occurs when Q changes end block Sync;
Try out an example using this feature in EDA Playground
case ADDRESS is when 0 => -- Select a single value A <= '1'; when 1 => A <= '1'; -- More than one statement in a branch B <= '1'; when 2 to 15 => -- Select a range of ADDRESS values C <= '1'; when 16 | 20 | 24 => -- Pick out several ADDRESS values B <= '1'; C <= '1'; D <= '1'; when others => -- Mop up the rest null; -- no action, no assignments made end case;
VHDL 2008 Examples
case? ag1 is -- Matching case when "---01010" => -- "-" is treated as don't care ag4 <= "000"; when "1101----" => -- Each value still must be unique ag4 <= "111"; when others => null; end case?; case a or b is -- Legal in VHDL 2008
-- anything after the two dashes is a comment -- but only until the end of a line
VHDL 2008 Examples
/* This is a VHDL 2008 block comment. It can span multiple lines, and include single line comments. However you cannot nest other block comments */ a <= /* you can even add one here */ b#101#;
Try out an example using this feature in EDA Playground
component Counter generic (N: INTEGER); port (Clock, Reset, Enable: in STD_LOGIC; Q: buffer STD_LOGIC_VECTOR (N-1 downto 0)); end component;
Try out an example using this feature in EDA Playground
L: Equal <= '1' when A = B else '0'; NextState <= Idle when State = Clear else Start when State = Idle else Stop when State = Start else Clear; Flipflop: Q <= D when Rising_edge(Clock); Latch: Q <= D when Enable = '1' else unaffected;
Try out an example using this feature in EDA Playground
architecture FullyBound of Top is component Blk port (A: in Int8; F: out Int8); end component; for B1: Blk use entity Work.Blk(RTL); for B2: Blk use entity Work.GateLevelBlk(Synth) port map (IP => To_Vector(A), To_Int8(OP) => F); begin B1: Blk port map (A, F); B2: Blk port map (B, G); end architecture FullyBound;
Try out an example using this feature in EDA Playground
use Work.Types.all; entity Top is -- Top level H/W description port (A, B: in Int8; F, G: out Int8); end entity Top; architecture Structure of Top is component Blk port (A: in Int8; F: out Int8); end component; begin B1: Blk port map (A, F); B2: Blk port map (B, G); end architecture Structure; ------------------------------------------ use Work.Types.all; entity Blk is -- Pre-Synthesis port (A: in Int8; F: out Int8); end entity Blk; architecture RTL of Blk is begin --... end architecture RTL; ------------------------------------------ library IEEE; use IEEE.STD_LOGIC_1164.all; entity GateLevelBlk is -- Post-Synthesis port (IP: in STD_LOGIC_VECTOR(7 downto 0); OP: out STD_LOGIC_VECTOR(7 downto 0)); end entity GateLevelBlk; architecture Synth of GateLevelBlk is begin --... end architecture Synth; ------------------------------------------ use Work.Types.all; configuration TopMixed of Top is for Structure for B1: Blk use entity Work.Blk(RTL); end for; for B2: Blk use entity Work.GateLevelBlk(Synth) port map (IP => To_Vector(A), To_Int8(OP) => F); end for; end for; end configuration TopMixed; ------------------------------------------ use Work.Types.all; entity Test is -- Test bench for Top end entity Test; architecture Bench of Test is component Top port (A, B: in Int8; F, G: out Int8); end component; signal A, B, F, G: Int8; begin --... Inst: Top port map (A, B, F, G); end architecture Bench; ------------------------------------------ configuration TestMixed of Test is for Bench for all: Top use configuration Work.TopMixed; end for; end for; end configuration TestMixed;
Try out an example using this feature in EDA Playground
constant Width: POSITIVE := 8; constant Mask: STD_LOGIC_VECTOR := "001000011111"; -- Range determined by length of string constant Mask: STD_LOGIC_VECTOR := 12B"001000011111"; constant Mask: STD_LOGIC_VECTOR := 12X"10f"; -- VHDL 2008 Range determined by specifying size directly
Try out an example using this feature in EDA Playground
context c1 is library IEEE; use IEEE.STD_LOGIC_1164.all; use STD.env.all; end; context work.c1; entity testbench is end testbench;
Try out an example using this feature in EDA Playground
disconnect Foo: STD_LOGIC after 10 NS;
Try out an example using this feature in EDA Playground
library IEEE; use IEEE.STD_LOGIC_1164.all; use IEEE.NUMERIC_STD.all; entity Counter is generic (N: INTEGER); port (Clock, Reset, Enable: in STD_LOGIC; Q: buffer STD_LOGIC_VECTOR (N-1 downto 0)); end entity Counter;
Try out an example using this feature in EDA Playground
type STD_ULOGIC is ('U', 'X', '0', '1', 'Z', 'W', 'L', 'H', '-'); type StateType is (Idle, Start, Stop, Clear);
package ENV is procedure STOP (STATUS : INTEGER); procedure STOP; procedure FINISH (STATUS : INTEGER); procedure FINISH; function RESOLUTION_LIMIT return DELAY_LENGTH; end package ENV;
Try out an example using this feature in EDA Playground
L1: loop L2: for I in A'RANGE loop if A(I) = 'U' then exit L1; -- Leave outer loop L1 end if; exit when I = N; -- Leave inner loop L2 end loop L2; -- ... end loop L1;
A + B not A (A nand B) nor C A(7 downto 0) -- name '0' -- character (others => '0') -- aggregate TO_INTEGER(V) -- function call or indexed name T'(A, B) -- qualified expression new T -- allocation
VHDL 2008 Example
sel1 <= s1 and s2 and addr ?<= 12X"345"; res <= and s7; -- unary and operation
VHDL 2008 only
Try out an example using this feature in EDA Playground
<<signal .testbench.top.cpu.alu.val : busType>> alias aval is <<variable .testbench.top.cpu.reg8 : INTEGER>>; <<signal .testbench.top.cpu.alua : INTEGER>> <= force 7;
Try out an example using this feature in EDA Playground
procedure FILE_OPEN (file F: FT; External_name: in STRING; Open_kind: in FILE_OPEN_KIND := READ_MODE); procedure FILE_OPEN (Status: out FILE_OPEN_STATUS; file F: FT; External_name: in STRING; Open_kind: in FILE_OPEN_KIND := READ_MODE); procedure FILE_CLOSE (file F: FT); procedure READ (file F: FT; VALUE: out TM); procedure WRITE (file F: FT; VALUE: in TM); function ENDFILE (file F: FT) return BOOLEAN; type T2 is file of T1; file F: T2 is out "filename"; -- VHDL'87 file F: T2 open Write_mode is "filename"; -- VHDL'93 etc.
package fixed_pkg is new IEEE.fixed_generic_pkg generic map(fixed_round_style => IEEE.fixed_float_types.fixed_round, .. ); -- other generics use IEEE.fixed_pkg.all; -- use fixed point package --... signal x, y : ufixed(3 downto -8); -- 4 bits numeric, 8 bits fractional, decimal right of 0 signal z, w : sfixed(7 downto -24); -- sign bit, 7 bits numeric, 24 bits fractional x <= to_ufixed(1.5, 3,-8); -- REAL to ufixed w <= to_sfixed(-7.3, 7, -24); -- REAL to sfixed
Try out an example using this feature in EDA Playground
type T is range 0.0 to 1.0; package float_pkg is new IEEE.float_generic_pkg generic map(float_exponent_width => 8,.. ); -- map all other generics use IEEE.float_pkg.all; --... signal a : float(8 downto -23) := 32X"deadbeef";
Try out an example using this feature in EDA Playground
type StateType is (Idle, Start, Stop, Clear); -- ... for I in 0 to 7 loop V := V xor A(I); for J in StateType loop S <= J; wait for 10 NS; end loop; end loop;
Try out an example using this feature in EDA Playground
package P is -- Conversion function function To_STD_LOGIC_VECTOR (Value, Width: INTEGER) return STD_LOGIC_VECTOR; -- Overloaded operator function "+" (A, B: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; end package P; package body P is function To_Std_logic_vector (Value, Width: INTEGER) return STD_LOGIC_VECTOR is variable V: INTEGER := Value; variable Result: STD_LOGIC_VECTOR (1 to Width); begin for I in Result'REVERSE_RANGE loop if V mod 2 = 1 then Result(I) := '1'; else Result(I) := '0'; end if; if V >= 0 then V := V / 2; else V := (V - 1) / 2; end if; end loop; return Result; end function To_Std_logic_vector; function "+" (A, B: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR is variable LV: STD_LOGIC_VECTOR(A'Length-1 downto 0); variable RV: STD_LOGIC_VECTOR(B'Length-1 downto 0); variable Result: STD_LOGIC_VECTOR(A'Length-1 downto 0); variable Carry: STD_LOGIC := '0'; begin LV := A; RV := B; assert A'Length = B'Length report "function +: operands have different widths" severity Failure; for I in Result'Reverse_range loop Result(I) := LV(I) xor RV(I) xor Carry; Carry := (LV(I) and RV(I)) or (LV(I) and Carry) or (RV(I) and Carry); end loop; return Result; end function "+"; end package body P;
B := To_Std_logic_vector(J, 2+2); C := IEEE.NUMERIC_STD."+" (L => A, R => B);
Try out an example using this feature in EDA Playground
G1: for I in 1 to Depth generate L: BLK port map (A(I), B(I+1)); -- Repeated instance end generate G1; G2: if Option = TRUE generate process -- Process is only created begin -- if Option is TRUE --... end process; end generate;
VHDL 2008 Examples
G3: if Option = serial generate process -- Process is only created begin -- if Option is serial --... end process; elsif Option = parallel generate process begin --... end process; else generate process begin --... end process; end generate; G4: case devType generate when opt1 => process --... end process; when opt2 => process --... end process; when others => process --... end process; end generate;
Try out an example using this feature in EDA Playground
generic (N, M: Positive; Mask: STD_LOGIC_VECTOR := "11111111");
VHDL 2008 example
Try out a VHDL 2008 example using EDA Playground
Try out a Generic Package example using EDA Playground
generic (Type mydatatype);
Try out an example using this feature in EDA Playground
architecture Structure of Ent is component NAND2 generic (TPLH, TPHL: TIME := 0 NS); port (A, B: in STD_LOGIC; F : out STD_LOGIC); end component; begin G1: NAND2 generic map (1.9 NS, 2.8 NS) port map (N1, N2, N3); G2: NAND2 generic map (TPLH => 2 NS, TPHL => 3 NS) port map (N4, N5, N6); end architecture Structure;
VHDL 2008 Example
package mypack is generic(dataWidth, addressWidth : intger); --... package small is new work.mypack generic map (dataWidth => 16, addressWidth => 4);
Try out an example using this feature in EDA Playground
architecture RTL of Ent is group Operations is (signal <>); group Adders : Operations (X, Y, Z); begin A1: X <= A + B; A2: Y <= C + D; A3: Z <= E + F; end architecture RTL;
Try out an example using this feature in EDA Playground
if C1 = '1' and C2 = '1' then V := not V; W := '0'; if C3 = '0' then X := A; elsif C4 = '0' then X := B; else X := C; end if; end if; --------------------------------------------- Mux: process (Sel, A, B) begin if Sel = '0' then -- Synthesis gives multiplexer F <= A; else F <= B; end if; end process; --------------------------------------------- Latch: process (En, D) begin if En = '1' then Q <= D; -- Synthesis of incomplete assignment gives -- transparent latch end if; end process; --------------------------------------------- Dtype: process begin wait until Clock = '1'; if En = '1' then Q <= D; -- Synthesis gives flip-flop end if; -- Output is recirculated through a multiplexer end process; --------------------------------------------- DtypeR: process (Reset, Clock) begin if Reset = '0' then -- Synthesis gives asynchronous reset Q <= '0'; elsif RISING_EDGE(Clock) then Q <= D; -- Synthesis gives flip-flop end if; end process;
VHDL 2008 - First Example Rewritten
if C1 and C2 then V := not V; W := '0'; if not C3 then X := A; elsif not C4 then X := B; else X := C; end if; end if;
G1: NAND2 generic map (1.2 NS) port map (N1, N2, N3); G2: entity WORK.Counter(RTL) port map (Clk, Rst, Count);
Try out an example using this feature in EDA Playground
type INT is range -8 to 7;
library IEEE, Project;
Try out an example using this feature in EDA Playground
loop wait until Clock = '1'; exit when Reset = '1'; Div2 <= not Div2; end loop;
Try out an example using this feature in EDA Playground
x = maximum (BIT_VECTOR'("110"), BIT_VECTOR'("1010")); -- x = "110" MINIMUM(100, 50) ; -- returns 50 MAXIMUM('x', 'y'); -- returns 'y' MINIMUM(STRING'("abc")); -- returns 'a'
A_99_Z -- Identifier \$%^&*()\ -- Extended identifer "+" -- Operator IEEE.STD_LOGIC_1164."nand" -- Selected name RecordVariable.ElementName -- Selected name Vector(7) -- Indexed name Matrix(I, J, K) -- Indexed name Vector(23 downto 16) -- Slice name Vector(J to K) -- Slice name Clock'EVENT -- Attribute name
VHDL 2008 Example
<<signal .top.adder.sum : STD_LOGIC_VECTOR>> -- external name
Link := new STD_LOGIC_VECTOR(7 downto 0); NewPointer := new Word'(Link, "10000000");
Try out an example using this feature in EDA Playground
L1: loop L2: for I in A'RANGE loop next when I = N; -- Jump to next iteration of inner loop L2 if A(I) = 'U' then next L1; -- Jump to top of outer loop L1 end if; end loop L2; --... end loop L1;
case Flag is when TRUE => Q := null; -- null value when FALSE => null; -- null statement end case;
30 = 3E1 = 16#1E# = 2#11_11#e1 30.0 = 300.0e-1 = 16#1E.0# = 2#11.11#E+3
Try out an example using this feature in EDA Playground
library IEEE; use IEEE.STD_LOGIC_1164.all; use IEEE.NUMERIC_STD.all; entity Counter is port (Clock, Reset : in STD_LOGIC; Q : out STD_LOGIC_VECTOR(7 downto 0)); end entity; architecture RTL of Counter is signal Count : UNSIGNED(7 downto 0); begin process (Clock , Reset) begin if Reset = '1' then Count <= (others => '0'); elsif Rising_edge(Clock) then Count <= Count + 1; end if; end process; Q <= STD_LOGIC_VECTOR(Count); end architecture;
Try out an example using this feature in EDA Playground
process variable SignedVar : SIGNED(7 downto 0) := "11111111"; variable UnsignedVar: UNSIGNED(7 downto 0); variable SLvectorVar: STD_LOGIC_VECTOR(7 downto 0); variable IntegerVar : INTEGER; begin UnsignedVar := UNSIGNED(SignedVar); -- Type conversion SignedVar := SIGNED(UnsignedVar); SLvectorVar := STD_LOGIC_VECTOR(UnsignedVar); UnsignedVar := UNSIGNED(SLvectorVar); IntegerVar := TO_INTEGER(SignedVar); -- Conversion function SignedVar := TO_SIGNED(IntegerVar,8); IntegerVar := TO_INTEGER(UnsignedVar); UnsignedVar := TO_UNSIGNED(IntegerVar,8); IntegerVar := TO_INTEGER(UNSIGNED(SlvectorVar)); SLvectorVar := STD_LOGIC_VECTOR(TO_SIGNED(IntegerVar,8)); end process;
control <= '1' when c=x else '0'; control <= c?=x;
Try out an example using this feature in EDA Playground
library IEEE; use IEEE.STD_LOGIC_1164.all; package UTILITIES is constant Size: Natural; -- Deferred constant subtype Byte is STD_LOGIC_VECTOR(7 downto 0); -- Subprogram declaration... function PARITY (V: Byte) return STD_LOGIC; end package UTILITIES; package body UTILITIES is constant Size: Natural := 16; -- Subprogram body... function PARITY (V: Byte) return STD_LOGIC is variable B: STD_LOGIC := '0'; begin for I in V'RANGE loop B := B xor V(I); end loop; return B; end function PARITY; end package body UTILITIES;
VHDL 2008 Example
library IEEE; use IEEE.STD_LOGIC_1164.all; package mypack is generic (dataWidth, addressWidth : INTEGER); subtype busTp is STD_LOGIC_VECTOR(dataWidth-1 downto 0); subtype addrTp is STD_LOGIC_VECTOR(addressWidth-1 downto 0); type memTp is array (0 to 2**addressWidth-1) of busTp; end package; package small is new work.mypack generic map (dataWidth => 16, addressWidth => 4);
Try out an example using this feature in EDA Playground
type Distance is range 0 to INTEGER'HIGH units micron; millimetre = 1000 micron; centimetre = 10 millimetre; metre = 100 centimetre; end units;
port (Clock, Reset: in STD_LOGIC; Q: buffer STD_LOGIC_VECTOR(7 downto 0); Status: out STD_LOGIC_VECTOR);
Try out an example using this feature in EDA Playground
component COUNTER port (CLK, RESET: in STD_LOGIC; UpDown: in STD_LOGIC := '0'; -- default value Q: out STD_LOGIC_VECTOR(3 downto 0)); end component; --... -- Positional association... G1: COUNTER port map (Clk32MHz, RST, open, Count); -- Named association (order doesn't matter)... G2: COUNTER port map ( RESET => RST, CLK => Clk32MHz, Q(3) => Q2MHz, Q(2) => Q1MHz, Q(1 downto 0) => Cnt2, UpDown => open); -- unconnected
VHDL 2008 Example
Try out an example using this feature in EDA Playground
G1: COUNTER port map (Clk32MHz, RST, a or b ?= c, Count);
Try out an example using this feature in EDA Playground
procedure ASSIGN (signal Clock: in STD_LOGIC; Values: STD_LOGIC_VECTOR; signal X, Y: out STD_LOGIC; variable V, W: out STD_LOGIC; PAUSE: TIME := 10 NS) is begin if Clock'EVENT and Clock = '1' then X <= Values(0); Y <= Values(1); V := Values(2); W := Values(3); wait for PAUSE; end if; end procedure ASSIGN; -- Procedure call ASSIGN (Clock, "0101", S1, S2, V1, V2);
Try out an example using this feature in EDA Playground
procedure Write (L: inout Line; Value: in STD_LOGIC_VECTOR; Justified: in Side := Right; Field: in Width := 0); --... Write (Buff, A, Left, 8); -- Positional association Write (Buff, C); Write (Justified => Left, Field => 12, L => Buff, Value => D); -- Named association
Try out an example using this feature in EDA Playground
process (all) -- VHDL 2008 begin --... -- Outputs assigned for all inputs automatically --... -- No feedback end process; -- Gives pure combinational logic ---------------------------------------------- process (Inputs) -- All inputs in sensitivity list begin --... -- Outputs assigned for all input conditions --... -- No feedback end process; -- Gives pure combinational logic ---------------------------------------------- process (Inputs) -- All inputs in sensitivity list begin if Enable = '1' then --... -- Latched actions end if; end process; -- Gives transparent latches + logic ---------------------------------------------- process (Clock) -- Clock only in sensitivity list begin if Rising_edge(Clock) then -- Test clock edge only --... -- Synchronous actions end if; end process; -- Gives flip-flops + logic ---------------------------------------------- process (Clock, Reset) -- Clock and reset only in sensitivity list begin if Reset = '0' then -- Test active level of asynchronous reset --... -- Asynchronous actions elsif Rising_edge(Clock) then -- Test clock edge only --... -- Synchronous actions end if; end process; -- Gives flip-flops + logic ---------------------------------------------- process -- No sensitivity list begin wait until Rising_edge(Clock); --... -- Synchronous actions end process; -- Gives flip-flops + logic Counter: process (Reset, Clock) begin if Reset = '0' then -- Asynchronous reset Count <= (others => '0'); elsif Rising_edge(Clock) then if Load = '0' then -- Synchronous load Count <= Data; else Count <= Count + 1; end if; end if; end process Counter; signal StopClock: BOOLEAN; signal Clk: STD_LOGIC; constant Period: Time := 10 NS; subtype Int8 is STD_LOGIC_VECTOR(7 downto 0); signal A, B: Int8; type Operation is (Load, Store, Move, Halt); signal Op: Operation; --... ClockGenerator: process begin while not StopClock loop Clk <= '0'; wait for Period/2; Clk <= '1'; wait for Period/2; end loop; wait; end process ClockGenerator; Stimulus: process type Table is array (Natural range <>) of Int8; constant Lookup: Table := ("00000000", "00000001", "00000011", "00001000", "00001111", "10000000", "11111000", "11111111"); begin for L in 1 to 2 loop for I in Lookup'Range loop B <= Lookup(I); for J in Lookup'Range loop A <= Lookup(J); for K in Operation loop Op <= K; wait for Period; end loop; end loop; end loop; StopClock <= True; -- Flag to stop clock generator process end loop; wait; end process Stimulus; process (all) is -- VHDL 2008 begin c <= a or b; -- c is assigned whenever a or b changes end process;
Try out an example using this feature in EDA Playground
subtype T is STD_LOGIC_VECTOR(1 to 2); --... if U > UNSIGNED'("10000000") then -- (1) WRITE (L, STRING'("Hello")); -- (2) V := (others => T'(others => '1')); -- (3) case T'(A, B) is -- (4)
Try out an example using this feature in EDA Playground
subtype INT is INTEGER range 0 to 7; subtype V1 is STD_LOGIC_VECTOR(INT); subtype V2 is INTEGER range V1'REVERSE_RANGE; --... for I in V2 range 3 downto 0 loop -- ...
Try out an example using this feature in EDA Playground
type Floating is record Sign: Bit; Mantissa, Exponent: INTEGER; end record; variable A, B: Floating; --... A.Mantissa := A.Mantissa + B.Mantissa; B := (Sign => '0', Mantissa => 1, Exponent => -1);
report "Simulation finished" severity Note;
Try out an example using this feature in EDA Playground
return A + B;
Try out an example using this feature in EDA Playground
Mux: with S select F <= A when "000", B when "001", C when "010" | "011" | "100", D when others;
VHDL 2008 Example
Pri: with P select? -- the "-" is treated as don't care Q <= X when "1-", Y when "01-", Z when others;
Try out an example using this feature in EDA Playground
type T is protected -- A new kind of type definition impure function Get return NATURAL; -- "Methods" procedure Increment (Inc: INTEGER); end protected T; type T is protected body variable Count: NATURAL; -- The shared data impure function Get return NATURAL is begin -- Each subprogram gives exclusive access to the variable return Count; end function Get; procedure Increment (Inc: INTEGER) is begin Count := Count + Inc; end procedure Increment; end protected body T; shared variable V: T; -- Shared variables must have a protected type
Try out an example using this feature in EDA Playground
signal A, B: STD_LOGIC_VECTOR(3 downto 0) := "ZZZZ";
VHDL 2008 Example
A <= force "1111"; -- VHDL 2008 A <= release; -- VHDL 2008
A <= B; A <= B nand C; A <= B nand C after 0.2 NS; (P, Q, R) <= T'("010"); H <= "00", "01" after 10 NS, "10" after 20 NS;
package STANDARD is type BOOLEAN is (FALSE, TRUE); type BIT is ('0', '1'); type CHARACTER is ( NUL, SOH, STX, ETX, EOT, ENQ, ACK, BEL, BS, HT, LF, VT, FF, CR, SO, SI, DLE, DC1, DC2, DC3, DC4, NAK, SYN, ETB, CAN, EM, SUB, ESC, FSP, GSP, RSP, USP, ' ', '!', '"', '#', '$', '%', '&', ''', '(', ')', '*', '+', ',', '-', '.', '/', '0', '1', '2', '3', '4', '5', '6', '7', '8', '9', ':', ';', '<', '=', '>', '?', '@', 'A', 'B', 'C', 'D', 'E', 'F', 'G', 'H', 'I', 'J', 'K', 'L', 'M', 'N', 'O', 'P', 'Q', 'R', 'S', 'T', 'U', 'V', 'W', 'X', 'Y', 'Z', '[', '\', ']', '^', '_', '`', 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h', 'i', 'j', 'k', 'l', 'm', 'n', 'o', 'p', 'q', 'r', 's', 't', 'u', 'v', 'w', 'x', 'y', 'z', '{', '|', '}', '~', DEL); -- VHDL'93 etc. include all 256 ASCII characters type SEVERITY_LEVEL is (NOTE, WARNING, ERROR, FAILURE); type INTEGER is range implementation_defined; type REAL is range implementation_defined; type TIME is range implementation_defined units fs; ps = 1000 fs; ns = 1000 ps; us = 1000 ns; ms = 1000 us; sec = 1000 ms; min = 60 sec; hr = 60 min; end units; -- function that returns the current simulation time: subtype DELAY_LENGTH is TIME range 0 FS to TIME'HIGH; pure function NOW return DELAY_LENGTH; subtype NATURAL is INTEGER range 0 to INTEGER'HIGH; subtype POSITIVE is INTEGER range 1 to INTEGER'HIGH; type STRING is array (POSITIVE range <>) of CHARACTER; type BOOLEAN_VECTOR is array (NATURAL range <>) of BOOLEAN; type BIT_VECTOR is array (NATURAL range <>) of BIT; type INTEGER_VECTOR is array (NATURAL range <>) of INTEGER; type REAL_VECTOR is array (NATURAL range <>) of REAL; type TIME_VECTOR is array (NATURAL range <>) of TIME; type FILE_OPEN_KIND is (READ_MODE, WRITE_MODE, APPEND_MODE); type FILE_OPEN_STATUS is (OPEN_OK, STATUS_ERROR, NAME_ERROR, MODE_ERROR); attribute FOREIGN: STRING; end STANDARD;
package STD_LOGIC_1164 is type Std_ulogic is ( 'U', -- Uninitialized 'X', -- Forcing Unknown '0', -- Forcing 0 '1', -- Forcing 1 'Z', -- High Impedance 'W', -- Weak Unknown 'L', -- Weak 0 'H', -- Weak 1 '-'); -- Don't care type Std_ulogic_vector is array (NATURAL range <>) of Std_ulogic; function Resolved (S: Std_ulogic_vector) return Std_ulogic; subtype STD_LOGIC is Resolved Std_ulogic; type STD_LOGIC_VECTOR is array (NATURAL range <>) of STD_LOGIC; subtype X01 is Resolved Std_ulogic range 'X' to '1'; subtype X01Z is Resolved Std_ulogic range 'X' to 'Z'; subtype UX01 is Resolved Std_ulogic range 'U' to '1'; subtype UX01Z is Resolved Std_ulogic range 'U' to 'Z'; function "and" (L, R: Std_ulogic) return UX01; function "nand" (L, R: Std_ulogic) return UX01; function "or" (L, R: Std_ulogic) return UX01; function "nor" (L, R: Std_ulogic) return UX01; function "xor" (L, R: Std_ulogic) return UX01; function "xnor" (L, R: Std_ulogic) return UX01; function "not" (L: Std_ulogic) return UX01; function "and" (L, R: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function "and" (L, R: Std_ulogic_vector) return Std_ulogic_vector; function "nand" (L, R: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function "nand" (L, R: Std_ulogic_vector) return Std_ulogic_vector; function "or" (L, R: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function "or" (L, R: Std_ulogic_vector) return Std_ulogic_vector; function "nor" (L, R: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function "nor" (L, R: Std_ulogic_vector) return Std_ulogic_vector; function "xor" (L, R: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function "xor" (L, R: Std_ulogic_vector) return Std_ulogic_vector; function "xnor" (L, R: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function "xnor" (L, R: Std_ulogic_vector) return Std_ulogic_vector; function "not" (L: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function "not" (L: Std_ulogic_vector) return Std_ulogic_vector; function To_Bit (S: Std_ulogic; Xmap: BIT := '0') return BIT; function To_Bitvector (S: STD_LOGIC_VECTOR; Xmap: BIT:='0') return BIT_VECTOR; function To_Bitvector (S: Std_ulogic_vector; Xmap: BIT:='0') return BIT_VECTOR; function To_StdULogic (B: BIT) return Std_ulogic; function To_StdLogicVector (B: BIT_VECTOR) return STD_LOGIC_VECTOR; function To_StdLogicVector (S: Std_ulogic_vector) return STD_LOGIC_VECTOR; function To_StdULogicVector(B: BIT_VECTOR) return Std_ulogic_vector; function To_StdULogicVector(S: STD_LOGIC_VECTOR) return Std_ulogic_vector; function To_X01 (S: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function To_X01 (S: Std_ulogic_vector) return Std_ulogic_vector; function To_X01 (S: Std_ulogic) return X01; function To_X01 (B: BIT_VECTOR) return STD_LOGIC_VECTOR; function To_X01 (B: BIT_VECTOR) return Std_ulogic_vector; function To_X01 (B: BIT) return X01; function To_X01Z (S: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function To_X01Z (S: Std_ulogic_vector) return Std_ulogic_vector; function To_X01Z (S: Std_ulogic) return X01Z; function To_X01Z (B: BIT_VECTOR) return STD_LOGIC_VECTOR; function To_X01Z (B: BIT_VECTOR) return Std_ulogic_vector; function To_X01Z (B: BIT) return X01Z; function To_UX01 (S: STD_LOGIC_VECTOR) return STD_LOGIC_VECTOR; function To_UX01 (S: Std_ulogic_vector) return Std_ulogic_vector; function To_UX01 (S: Std_ulogic) return UX01; function To_UX01 (B: BIT_VECTOR) return STD_LOGIC_VECTOR; function To_UX01 (B: BIT_VECTOR) return Std_ulogic_vector; function To_UX01 (B: BIT) return UX01; function Rising_edge (signal S: Std_ulogic) return BOOLEAN; function Falling_edge (signal S: Std_ulogic) return BOOLEAN; function Is_X (S: Std_ulogic_vector) return BOOLEAN; function Is_X (S: STD_LOGIC_VECTOR) return BOOLEAN; function Is_X (S: Std_ulogic) return BOOLEAN; end STD_LOGIC_1164;
Try out an example using this feature in EDA Playground
"Hello" "0000XXXX" B"0000_0101" X"FFFF"
VHDL 2008 Example
10X"2ff" –- 10 specifies the number of bits
subtype STD_LOGIC is Resolved Std_ulogic; subtype MyBit is STD_LOGIC range '0' to '1'; subtype ShortVector is STD_LOGIC_VECTOR(1 downto 0);
Try out a Read example using EDA Playground
Try out a Write example using EDA Playground
signal A, B, G: BIT_VECTOR(3 downto 0); --... Monitor: process use STD.TEXTIO.all; file F: TEXT is out "test.txt"; -- VHDL'87 file F: TEXT open WRITE_MODE is "test.txt"; variable L: LINE; begin -- Strobe the signals... wait until Rising_edge(Clock); wait for Settling_time; WRITE (L, NOW, Left, 10); -- NOW = current simulation time WRITE (L, A, Right, 5); WRITE (L, B, Right, 5); WRITE (L, G, Right, 5); WRITELINE (F, L); end process; -- Reading a text file signal A, B: BIT_VECTOR(3 downto 0); --... Stimulus: process use STD.TEXTIO.all; file F: TEXT is in "vectors.txt"; -- VHDL'87 file F: TEXT open READ_MODE is "vectors.txt"; variable L: LINE; variable TimeWhen: TIME; variable Avalue, Bvalue: BIT_VECTOR(3 downto 0); begin while not ENDFILE(F) loop READLINE (F, L); READ (L, TimeWhen); READ (L, Avalue); READ (L, Bvalue); wait for TimeWhen - NOW; -- Wait until an absolute time A <= Avalue; B <= Bvalue; end loop; wait; end process; package TEXTIO is -- Type definitions for Text I/O type LINE is access STRING; -- a LINE is a pointer to a STRING value type TEXT is file of STRING; -- a file of variable-length ASCII records type SIDE is (RIGHT, LEFT); -- for justifying output data within fields subtype WIDTH is NATURAL; -- for specifying widths of output fields function JUSTIFY (VALUE : STRING; JUSTIFIED : SIDE := RIGHT; FIELD_WIDTH := 0) RETURN STRING; -- VHDL 2008 -- Standard Text Files (VHDL'87 version is similar) file INPUT: TEXT open READ_MODE is "STD_INPUT"; file OUTPUT: TEXT open WRITE_MODE is "STD_OUTPUT"; -- Input Routines for Standard Types procedure READLINE (variable f: TEXT; L: inout LINE); procedure READ (L: inout LINE; VALUE: out BIT; GOOD: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out BIT); procedure READ (L: inout LINE; VALUE: out BIT_VECTOR; GOOD: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out BIT_VECTOR); procedure READ (L: inout LINE; VALUE: out BOOLEAN; GOOD: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out CHARACTER; GOOD: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out CHARACTER); procedure READ (L: inout LINE; VALUE: out INTEGER; GOOD: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out INTEGER); procedure READ (L: inout LINE; VALUE: out REAL; GOOD: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out REAL); procedure READ (L: inout LINE; VALUE: out STRING; GOOD: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out STRING); procedure READ (L: inout LINE; VALUE: out TIME; GOOD: out BOOLEAN); procedure READ (L: inout LINE; VALUE: out TIME); -- The following were added in VHDL 2008 procedure SREAD (L: inout LINE; VALUE: out STRING; STRLEN: out NATURAL); alias STRING_READ is SREAD [LINE, STRING, NATURAL]; alias BREAD is READ [LINE, BIT_VECTOR, BOOLEAN]; alias BREAD is READ [LINE, BIT_VECTOR]; alias BINARY_READ is READ [LINE, BIT_VECTOR, BOOLEAN]; alias BINARY_READ is READ [LINE, BIT_VECTOR]; procedure OREAD (L: inout LINE; VALUE: out BIT_VECTOR; GOOD: out BOOLEAN); procedure OREAD (L: inout LINE; VALUE: out BIT_VECTOR); alias OCTAL_READ is OREAD [LINE, BIT_VECTOR, BOOLEAN]; alias OCTAL_READ is OREAD [LINE, BIT_VECTOR]; procedure HREAD (L: inout LINE; VALUE: out BIT_VECTOR; GOOD: out BOOLEAN); procedure HREAD (L: inout LINE; VALUE: out BIT_VECTOR); alias HEX_READ is HREAD [LINE, BIT_VECTOR, BOOLEAN]; alias HEX_READ is HREAD [LINE, BIT_VECTOR]; -- Output Routines for Standard Types procedure WRITELINE (F: out TEXT; L: inout LINE); -- added in VHDL 2008 procedure TEE (file F: TEXT; L: inout LINE); procedure WRITE (L: inout LINE; VALUE : in BIT; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0); procedure WRITE (L: inout LINE; VALUE: in BIT_VECTOR; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0); procedure WRITE (L: inout LINE; VALUE: in BOOLEAN; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0); procedure WRITE (L: inout LINE; VALUE: in CHARACTER; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0); procedure WRITE (L: inout LINE; VALUE: in INTEGER; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0); procedure WRITE (L: inout LINE; VALUE: in REAL; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0; DIGITS: in NATURAL := 0); procedure WRITE (L: inout LINE; VALUE: in STRING; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0); procedure WRITE (L: inout LINE; VALUE: in TIME; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0; UNIT: in TIME := ns); -- added in VHDL 2008 alias SWRITE is WRITE [LINE, STRING, SIDE, WIDTH]; alias STRING_WRITE is WRITE [LINE, STRING, SIDE, WIDTH]; alias BWRITE is WRITE [LINE, BIT_VECTOR, SIDE, WIDTH]; alias BINARY_WRITE is WRITE [LINE, BIT_VECTOR, SIDE, WIDTH]; procedure OWRITE (L: inout LINE; VALUE: in BIT_VECTOR; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0); alias OCTAL_WRITE is OWRITE [LINE, BIT_VECTOR, SIDE, WIDTH]; procedure HWRITE (L: inout LINE; VALUE: in BIT_VECTOR; JUSTIFIED: in SIDE := RIGHT; FIELD: in WIDTH := 0); alias HEX_WRITE is HWRITE [LINE, BIT_VECTOR, SIDE, WIDTH]; -- function ENDFILE(F: in TEXT) return BOOLEAN; -- ENDFILE is implicitly declared for all file types end TEXTIO;
Try out an example using this feature in EDA Playground
signal I: INTEGER; signal R: REAL; --... R <= REAL(I) * 2.0; type STD_LOGIC_VECTOR is array (Natural range <>) of STD_LOGIC; type UNSIGNED is array (Natural range <>) of STD_LOGIC; -- STD_LOGIC_VECTOR and UNSIGNED are closely related signal S: STD_LOGIC_VECTOR(7 downto 0); signal U: UNSIGNED(7 downto 0); --... S <= STD_LOGIC_VECTOR(U); U <= UNSIGNED(S);
use IEEE.STD_LOGIC_1164.all; -- The package name only use WORK.Arith_Ops; -- All the entities in the library use CMOS_TECH.all;
Try out an example using this feature in EDA Playground
variable V, W: INTEGER range 0 to 7 := 7;
process variable V, W: STD_LOGIC; begin wait until Clock = '1'; V := A nand W; -- a nand gate V := V nor B; -- a nor gate W := D; -- a flip-flop S <= V; -- a flip-flop end process; -- Other examples (used within a process) V := V + 1; (V, W) := X;
Try out an example using this feature in EDA Playground
constant Period: TIME := 25 NS; --... Stimulus: process begin A <= "0000"; B <= "0000"; wait for Period; A <= "1111"; wait for Period; B <= "1111"; wait for Period; wait; end process;
Try out an example using this feature in EDA Playground
while Going loop Count := Count + 1; wait until Clock = '1'; end loop;