top of page

VHDL 2008: a powerful unexplored language

Since the publication of the first IEEE standard in 1987 several revised versions have appeared. The first, in 1993, had the most extensive changes. VHDL 2000 Edition introduced protected types and VHDL-2002 contains mainly minor changes. VHDL-2008 is the name of the new version of VHDL. As with the earlier revisions, this doesn’t radically alter the language, but it does provide a wider set of modifications than previously. The standard is now available from the IEEE and is known as IEEE Std. 1076-2008.

Summary of Changes to VHDL in VHDL-2008

The changes to VHDL that are proposed in VHDL-2008 fall broadly into these categories:

  • VHDL is enhanced significantly in some areas

  • Changes that make VHDL (slightly) less cumbersome to use

  • Existing separate VHDL standards are incorporated into the LRM

  • A number of smaller enhancements

​See Also You will find further information about the standardization of VHDL-2008 using these links:

VHDL-2008: Major Enhancements

The majority of changes to VHDL that VHDL-2008 introduces are useful and important, but relatively minor. However, the following represent major enhancements to the language.

  • PSL is integrated into VHDL

  • Package and subprogram generics

  • Generic types, subprograms and packages

  • New synthesizable fixed and floating point arithmetic packages

PSL is integrated into VHDL

VHDL already includes the assert statement, which is used for adding simple checkers to VHDL models. You assert that an expression evaluates to TRUE, meaning that you expect that this will be the case whenever the assertion is evaluated. If the expression is in fact FALSEthe simulator writes out an error message.

PSL (Property Specification Language) extends this idea by providing a syntax for describing the expected behaviour of a circuit over time and for checking that the VHDL code implements that behaviour. Until now, PSL statements could only be added to VHDL models as meta-comments (“comments” that a compiler may in fact interpret as extended syntax) or in separate files (vunits). For example:

--psl assert always req -> next[2] (grant);

VHDL-2008 now includes the simple subset of PSL as part of the standard VHDL syntax. All PSL keywords are now reserved in VHDL. (Using PSL’s simple subset means using PSL in a way that simulators can handle.) In VHDL-2008, the example given above can be written as a concurrent statement like this:

assert always req -> next[2] (grant);

Similarly, PSL declarations – for example, of clocks, properties and sequences – may be included in VHDL declarative regions. If a concurrent statement could be interpreted either as a VHDL assert statement or a PSL directive, the VHDL interpretation is used:

assert not (a and b);

is interpreted as VHDL, not PSL. Some PSL keywords are now reserved keywords in VHDL. For example, property, and sequence. Other PSL keywords only have a special meaning within PSL declarations and directives. For example, before is a keyword in PSL, but not in VHDL.

​Package and subprogram generics.​

In VHDL, generics have always been allowed on entities. This enables you to write parameterized design entities, such as an N-bit counter. VHDL-2008 allows generics on packages and subprograms too. This makes it more convenient to write flexible, re-usable code. For an example, see the synthesizable fixed and floating point packages below.

Generic types, subprograms and packages.

In VHDL generics are constants. In VHDL-2008 they may also be types, subprograms or packages.Here is an entity that has a type generic (data_type) and a subprogram generic (function increment). We can’t use the "+" operator in the architecture, because "+" is not supported for arbitrary data types.

library ieee; use ieee.std_logic_1164.all; entity incrementer is generic (type data_type; function increment (x: data_type) return data_type); port (I : in data_type; O : out data_type; inc : in std_logic); end entity mux; architecture RTL of mux is begin O <= increment(I) when inc = '1'; end architecture RTL;

This shows how we might instance this entity:

incr_inst : entity work.incrementer generic map ( data_type => std_logic_vector(7 downto 0), increment => add_one ) port map ( I => I, O => O, inc => ena );

New synthesizable fixed and floating point arithmetic packages.

One application of these extended generics is found with the new fixed and floating point arithmetic packages that are part of VHDL-2008. Here is part of the declaration of fixed_generic_pkg:

package fixed_generic_pkg is generic (fixed_round_style : fixed_round_style_type := fixed_round; fixed_overflow_style : fixed_overflow_style_type := fixed_saturate; -- ...

and here is part of the declaration of fixed_pkg :

package fixed_pkg is new IEEE.fixed_generic_pkg generic map ( fixed_round_style => IEEE.fixed_float_types.fixed_round, fixed_overflow_style_type => -- ...

Many of the enhancements in VHDL-2008 are intended to make VHDL easier to use. These are all fairly minor additions to the language or changes to the syntax. Nevertheless, they will make a real difference in day-to-day VHDL design.

  • New condition operator, ??

  • Enhanced bit string literals

  • Hierarchical names

  • Vectors in aggregates

  • Conditional and selected sequential statements

  • Extensions to generate

  • Simplified sensitivity lists

  • Arithmetic on std_logic_vector

​New condition operator, ??

How many times have you wanted to write something like this:

if A and B then ...

where A and B are STD_LOGIC? You haven’t been able to, because VHDL’s if statement requires a boolean expression, not a STD_LOGIC one. You have to write this instead:

if A = '1' and B = '1' then ...

VHDL-2008 introduces a new operator, ??. It ’s called the condition operator and it converts a STD_LOGIC expression to a BOOLEAN one: '1'and 'H' are considered TRUE and everything else FALSE. (It also converts BIT to BOOLEAN .) So you can now write this:

if ?? A and B then ...

or, even better ... In certain circumstances, ?? is applied implicitly. The condition expression of an if statement is one of those. So you can indeed now write:

if A and B then ...

​Enhanced bit string literals.

You use string literals as literal values of type STD_LOGIC_VECTOR or similar. For example,

signal Count : unsigned(7 downto 0);

...

Count <= "00000000";

In VHDL-1987, string literals provided, in effect, a way of expressing a vector as a binary number. VHDL-1993 introduced binary, octal and hexadecimal bit string literals:

Count <= B"0000_0000"; -- "_" is for readability only Count <= X"00"; -- Hex; O"..." is octal

One limitation in VHDL-1993 is that hexadecimal bit-string literals always contain a multiple of 4 bits, and octal ones a multiple of 3 bits. You can’t have a 10-bit hexadecimal bit-string literal, or one containing values other than 0, 1 or _, for example. In VHDL-2008, bit string literals are enhanced:

  • they may have an explicit width,

  • they may be declared as signed or unsigned,

  • they may include meta-values ('U', 'X', etc.)

Here are some examples:

variable S : std_logic_vector(5 downto 0); begin S := 6x"0f"; -- specify width 6 S := 6x"XF"; -- means "XX1111" S := 6SX"F"; -- "111111" (sign extension) S := 6Ux"f"; -- "001111" (zero extension) S := 6sb"11"; -- "111111" (binary format) S := 6uO"7"; -- "000111" (octal format)

Note that within bit string literals it is allowed to use either upper or lower case letters, i.e. F or f.

Hierarchical names.

Some of the new features in VHDL-2008 are intended for verification only, not for design. Verification engineers often want to write self-checking test environments. In VHDL this can be difficult as there is no easy way to access a signal or variable buried inside the design hierarchy from the top level of the verification environment. VHDL-2008 addresses this by introducing external names. An external name may refer to a (shared) variable, signal, or constant which is in another part of the design hierarchy. External names are embedded in double angle brackets << >> Special characters may be used to move up the hierarchy ^ and to root the path in a package @ . Some examples:

<< signal .tb.uut.o_n : std_logic >> -- hierarchical signal name << signal ^.^.a : std_logic >> -- signal a two levels above << variable @lib.pack.v : bit >> -- variable in a package pack

Other uses for external names include injecting errors from a test environment, and forcing and releasing values (see later).

Vectors in aggregates

VHDL aggregates allow a value to be made up from a collection individual array or record elements. For arrays, VHDL up to 1076-2002 allows syntax like this:

variable V : std_logic_vector(7 downto 0); begin V := (others => '0'); -- "00000000" V := ('1', '0', others => '0'); -- "10000000" V := (4 => '1', others => '0'); -- "00010000" V := (3 downto 0 => '0', others => '1'); -- "11110000" -- V := ("0000", others => '1'); -- illegal!

VHDL-2008 allows the use of a slice in an array aggregate. So for instance the examples above could be written:

V := (others => '0'); -- "00000000" V := ("10", others => '0'); -- "10000000" V := (4 => '1', others => '0'); -- "00010000" V := (3 downto 0 => '0', others => '1'); -- "11110000" V := ("0000", others => '1'); -- "00001111"

It is also possible to use aggregates as the target of an assignment, like this:

( S(3 downto 0), S(7 downto 4)) <= S; -- swap nibbles ( 3 downto 0 => S, 7 downto 4 => S) <= S; -- using named association

Conditional and selected sequential statements.

Historically there have been two styles of writing "decision" statements in VHDL - concurrent and sequential. And you had to get them correct - you could not use a conditional signal assignment such as...

z <= x when x > y else y;

in a process. VHDL-2008 relaxes this and allows a flip-flop to be modelled like this:

process(clock) begin if rising_edge(clock) then q <= '0' when reset else d; -- not allowed in VHDL 2002 end if; end process;

It is also permitted to use the selected signal assignment in a process:

process(clock) begin if rising_edge(clock) then with s select -- equivalent to a case statement q <= a when "00", b when "01", c when "10", d when "11"; end if; end process;

Extensions to generate.

VHDL-2008 makes the generate statement much more flexible. It is now allowed to use else and elsif. Also there is a case version of generate. This makes generate easier to use. Instead of writing

g1: if mode = 0 generate c1 : use entity work.comp(rtl1) port map (a => a, b=>b); end generate; g2: if mode = 1 generate c1 : use entity work.comp(rtl2) port map (a => a, b=>b); end generate; g3: if mode = 2 generate c1 : use entity work.comp(rtl3) port map (a => a, b=>b); end generate;

you can write:

g1: case mode generate when 0 => c1 : use entity work.comp(rtl1) port map (a => a, b=>b); when 1 => c1 : use entity work.comp(rtl2) port map (a => a, b=>b); when 2 => c1 : use entity work.comp(rtl3) port map (a => a, b=>b); end generate;

Note that within each branch, you can still declare local names which will not clash with names in the other branches (such as label c1 above). It is still possible to declare local objects within the branch using begin-end.

Simplified sensitivity lists.

The keyword all may be used in the context of a sensitivity list, to mean that all signals read in the process should be added to the sensitivity list, for example:

process(all) begin case state is when idle => if in1 then nextState <= Go1; end if; when Go1 => nextState <= Go2; when Go2 => nextState <= Idle; end case; end process;

This avoids a common problem where the author modifies a combination process and then forgets to update the sensitivity list, leading to a simulation/synthesis mis-match.

Arithmetic on std_logic_vector

VHDL has a well-designed package IEEE.Numeric_Std which creates two new data types unsigned and signed. However it would sometimes

be convenient to do arithmetic on std_logic_vector directly - treating it as either two's complement or unsigned. In the past this has mainly been achieved by using the non-standard std_logic_unsigned and std_logic_signed packages. VHDL-2008 addresses this issue by adding two new standard arithmetic packages, IEEE.Numeric_Std_Unsigned and IEEE.Numeric_Std_Signed.

VHDL-2008: Incorporates existing standards

VHDL-2008 includes standards that were in the past separate. These standards were only separate from the main VHDL standard because they were developed after the VHDL itself. This led to some "quirks"; for instance the std_match function which does a "don't care" comparison between std_logic_vectors was defined in the numeric_std package - even though none of the other functions and operators innumeric_std work on type std_logic_vector! Extra features have been added to the standard packages. While some of these standards are packages, VHDL-2008 also incorporates PSL and the VHDL Programming Interface (VHPI).

  • VHPI is included

  • Standard Packages are included

  • std_logic_1164 is extended

  • textio is extended

  • Context makes including packages is easier

VHPI is included

The VHDL Programming Interface 1076-2007c is a relatively new standard which defines a C interface to VHDL. The standard is complex and allows manipulation of the simulation process, static data, and dynamic data. From the point of view of VHDL-2008 all we need to know is that it is now included in VHDL!

Standard packages are included in VHDL

The original VHDL definition included only the types defined in the package std.standard. Over the years the following packages have been developed to work with VHDL:

  • IEEE.Numeric_Std

  • IEEE.Numeric_Bit

  • IEEE.Math_Real

  • IEEE.Math_Complex

  • IEEE.Std_logic_1164

All these packages are now incorporated into the main VHDL standard. In addition a number of packages have become very widely used even though they are not official standards. These are:

  • std_logic_unsigned

  • std_logic_signed

  • std_logic_textio

As mentioned previously The replacements for std_logic_unsigned and std_logic_signed are the new packages numeric_std_unsigned andnumeric_std_signed. The functionality of the std_logic_textio is now included in IEEE.std_logic_1164. The user may still include std_logic_textio, but the package is now just a "stub" - the functions are actually provided in IEEE.std_logic_1164.

std_logic_1164 is extended

Not only is std_logic_1164 incorporated into VHDL-2008, it has been improved. The main changes are

  • std_logic_vector is now a subtype of std_ulogic_vector which makes using both types together much easier

  • There are new operators and functions, including reduction operators, matching operators, minimum and maximum functions, shift operators, string conversion functions

Here are some examples of the new operators:

signal o : std_logic; signal x,y,v : std_logic_vector(2 downto 0);

o <= i1 when ?? sel else i2; -- intepret sel as boolean

o <= and v; -- reduction operator, returns std_ulogic

o <= x ?= y; -- ?= and ?/= work on std_(u)logic_vector -- ?= ?/= ?< ?<= ?> ?>= on std_(u)logic

The matching operators return the appropriate operand type, rather than boolean.

textio is extended

Of course textio has been part of VHDL since the original standard in 1987, so perhaps does not really belong in this section. However it has been extended in a way that incorporates features sometimes provided by other non-standard packages (for instance the Mentor SDK). So this section summarises what is new. VHDL-2008 includes additional functions to read and write std_logic and std_logic_vector (historically people used the non-standard std_logic_textio to provide these functions). There is now a function swrite to simplify writing string literals. Here is an example:

write(L, string'("-- start of file")); -- type qualification required swrite(L, "-- start of file"); -- no type qualification required

If you wanted to write text to both a file and to standard output, it was not easy to do in VHDL 2002 and earlier - the simplest solution was simply to call the writeline procedure twice, once for each destination. VHDL-2008 adds a procedure tee to do this for you:

tee(F, L); -- writes to file F *and* to standard output

If you want to explicitly flush a file without closing it, there is a procedure for that very purpose:

flush(F); -- flushes F to disk

The procedures formerly in std_logic_textio for hex and octal format writing are included in textio. In addition, there are overloaded implementations of to_string for many different data types. There is also a function called justify to format data without using the justification and field width parameters of the standard read and write functions. Here is a slightly contrived example showing some of these features:

write(L, justify(to_string(now,ns), field => 10) & justify(to_hstring(sel) , field => 2 ) );

Note the introduction of to_hstring as well.

Context makes including packages easier

Now all these packages are available, it can be a bit tedious adding all the appropriate package context clauses in front of your testbench or design. VHDL-2008 provides a way of grouping a set of library and use statements into a named context. Once the context is declared, it can be used repeatedly. For convenience there are some built-in contexts for common purposes such as writing synthesisable code. Here's an example which you might declare contexts for a site and a project:

context site_context is -- compiled into library sitelib library IEEE; use IEEE.std_logic_1164.all; use IEEE.numeric_std.all; use sitelib.sitepack.all; end context;

context proj1_context is -- compiled into library proj1lib library sitelib; context sitelib.site_context; use proj1lib.proj1pack.all; end context;

Now anyone on the proj1 project can just say

library proj1lib; context proj1lib.proj1_context;

and they have a project standard setup in two lines! The VHDL-2008 standard defines two built-in contexts as follows:

context IEEE_BIT_CONTEXT is library IEEE; use IEEE.numeric_bit.all; ene context IEEE_BIT_CONTEXT;

context IEEE_STD_CONTEXT is library IEEE; use IEEE.std_logic_1164.all; use IEEE.Numeric_Std.all; end context IEEE_STD_CONTEXT;

VHDL-2008: Small Changes

This page summarises a number other changes, most of which are quite small. Some of these have already been mentioned in passing on other pages, and are summarised here as well. These changes include:

  • New standard functions: minimum, maximum and to_string are defined for scalar and array types; to_bstring, to_binarystring, to_ostring,to_octalstring, to_hstring, and to_hexstring for arrays.

  • Function rising_edge is defined for type boolean.

  • Arrays and records may contain unconstrained elements.

  • These new array types are added: boolean_vector, integer_vector, real_vector, and time_vector.

  • “Matching” case statement, case?

  • force and release for signals.

  • /* */ block comments.

  • 'INSTANCE_NAME etc. extended for package and subprogram instantiation.

  • New standard environment package, ENV that includes procedures stop and finish and function resolution_limit.

  • IP encryption directives (protect) are added.

Below you'll find some more detail about the following changes:

  • New and changed standard functions

  • Array and record types

  • The matching case statement

  • Forcing and releasing signals

  • Block comments

  • Changes to 'INSTANCE_NAME

  • Standard environment package

  • IP Encryption

New and changed standard functions

VHDL-2008 defines two new functions minimum and maximum. These are defined for scalar or array types.

minimum(10,11) -- returns 10

-- bv1 contains "0111" bv2 contains "1000" maximum(bv1, bv2) -- returns "1000"

Note that comparison of vectors is not done numerically unless you include an arithmetic package - the arithmetic packages overload the above functions to operate arithmetically. Before VHDL-2008, the strength reduction functions were not defined consistently on signed, unsigned, and std_(u)logic_vector. In VHDL-2008 the following functions are now consistently defined on these types:

is_X to_X01 to_X01Z to_UX01 to_01

Array and record types

One of the main changes to composite types (array and record types) is that now you can use unconstrained array and record elements. For instance the following declarations are now legal:

type myArrayT is array (natural range <>) of std_logic_vector;

type myRecordT is record a : std_logic_vector; b : std_logic_vector; end record;

The language has also been extended to allow declaration of fully or partially constrained objects and types. For instance the above record type may be used to declare a fully constrained variable as follows:

variable R : myRecordT( a(7 downto 0), b(15 downto 0) );

In certain contexts (for instance when using unconstrained ports or procedure parameters) it is possible to use the keyword open to represent a dimension that should remain unconstrained. VHDL-2008 adds a number of new predefined array types as follows:

type boolean_vector is array (natural range <>) of boolean 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

The matching case statement

There is a new version of case which allows don't care behaviour, case?. Here is an example:

case? sel is when "1---" => o <= "11"; when "01--" => o <= "10"; when "001-" => o <= "01"; when "0001" => o <= "00"; when others => null; end case;

The comparison is carried out using the matching equality operator ?= which means that the don't care character '-' is truly treated as don't care, and also that (for instance) 'H' matches '1'. As for a regular case statement, each value of the expression at the top must be represented exactly once amongst the set of choices: when using pattern matching, you have to be careful that patterns that include the '-'do not overlap.

New and changed standard functions

VHDL-2008 defines two new functions minimum and maximum. These are defined for scalar or array types.

minimum(10,11) -- returns 10

-- bv1 contains "0111" bv2 contains "1000" maximum(bv1, bv2) -- returns "1000"

Note that comparison of vectors is not done numerically unless you include an arithmetic package - the arithmetic packages overload the above functions to operate arithmetically. Before VHDL-2008, the strength reduction functions were not defined consistently on signed, unsigned, and std_(u)logic_vector. In VHDL-2008 the following functions are now consistently defined on these types:

is_X to_X01 to_X01Z to_UX01 to_01

Array and record types

One of the main changes to composite types (array and record types) is that now you can use unconstrained array and record elements. For instance the following declarations are now legal:

type myArrayT is array (natural range <>) of std_logic_vector;

type myRecordT is record a : std_logic_vector; b : std_logic_vector; end record;

The language has also been extended to allow declaration of fully or partially constrained objects and types. For instance the above record type may be used to declare a fully constrained variable as follows:

variable R : myRecordT( a(7 downto 0), b(15 downto 0) );

In certain contexts (for instance when using unconstrained ports or procedure parameters) it is possible to use the keyword open to represent a dimension that should remain unconstrained. VHDL-2008 adds a number of new predefined array types as follows:

type boolean_vector is array (natural range <>) of boolean 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

The matching case statement

There is a new version of case which allows don't care behaviour, case?. Here is an example:

case? sel is when "1---" => o <= "11"; when "01--" => o <= "10"; when "001-" => o <= "01"; when "0001" => o <= "00"; when others => null; end case;

The comparison is carried out using the matching equality operator ?= which means that the don't care character '-' is truly treated as don't care, and also that (for instance) 'H' matches '1'. As for a regular case statement, each value of the expression at the top must be represented exactly once amongst the set of choices: when using pattern matching, you have to be careful that patterns that include the '-'do not overlap.

Forcing and releasing signals

For verification, it is sometimes convenient to be able to "override" the value of a signal. This can be used for error injection, for instance. Of course this is always possible using vendor-specific commands, typically written in Tcl. But VHDL-2008 allows this in pure VHDL. It is also possible to remove the overridden value using the release keyword. Finally it is possible to make a distinction between the effective and driving value of a signal (there are restrictions on ports depending on their mode).

<< tb.uut.s >> <= force '1'; -- inject error << tb.uut.s >> <= release; -- stop overriding

v <= force in '1'; -- force effective value v <= force out '0'; -- force driving value

v <= release in; -- release effective value v <= release out; -- release driving value

Block comments

With VHDL-2008 it is now possible to achieve the same confusing errors you can with a language like C, and comment out a big chunk of code by accident, with a delimited (block) comment. (Can you tell I'm not a big fan?).

/* s <= 1; r <= 2; */

Changes to 'INSTANCE_NAME

Both 'INSTANCE_NAME and 'PATH_NAME have been corrected so that they cope with shared variables of protected type (introduced in VHDL 2000), and overloaded operators. Previously the paths and instance strings produced by these attributes did not include operator names and shared variables.

Standard environment package

An additional environment package is added. This package allows VHDL code to control the simulator, and to find out the simulator time resolution. The package is std.env.

procedure stop(status:integer); prodedure stop;

procedure finish(status:integer); procedure finish;

function resolution_limit return delay_length;

stop causes a simulation to stop but not to quit. finish causes a simulation to quit. The resolution_limit function allows the user to find out the simulator resolution limit - for instance you could wait for a minimum time step using

wait for env.resolution_limit;

IP Encryption

VHDL-2008 has a means of specifying that a block of data is encrypted. This uses an additional feature - the tool directive. Tool directives are arbitrary words preceded by a backtick character `. The idea of tool directives is that they are interpreted by tools, they don't have any meaning to a VHDL compiler. For IP encryption, a set of predefined tool directives is defined as follows:

`protect begin `protect end `protect begin_protected `protect end_protected `protect author `protect author_info `protect encrypt_agent `protect encrypt_agent_info `protect key_keyowner `protect key_keyname `protect key_method `protect key_block `protect data_keyowner `protect data_keyname `portect data_methdo `protect data_block `protect digest_keyowner `protect digest_keyname `protect digest_key_method `protect digest_method `protect digest_block `protect encoding `protect viewport `protect decrypt_license `protect runtime_license `protect comment

Many of these tool directives have additional parameter values. Here's a short example of what some VHDL code might look like using IP encryption:

entity e is -- ports omitted end entity;

architecture RTL of e is `protect data_keyowner = "Campera User" `protect data_keyname = "Campera Key" `protect data_method = "rsa" `protect encoding = (enctype= "quoted-printable") `protect begin

-- code omitted begin -- code omitted

`protect end end architecture RTL;

bottom of page