_________________________________________
VHDL : VHSIC Hardware Description Language
VHDL Lecture Notes
Prof M R Bhujade
Department of Computer Science and Engineering
Copyright Prof M R Bhujade
Use of this material is permitted for personal educational use.
Copying and distributing without authours permission is violative of copyright act.
_____________________________
Origin : US governments’s Very High Speed Integrated Circuits Ptogram(VHSIC). The need for a standard language for describing the structure and the function of Integrated Circuits (Ics). The VHSIC Hardware Description Language (VHDL) was developed and subsequently adapted as a standard by IEEE .
Purpose of the language is to specify the design using structural and behavirol
aspects and simulate and verify the design thrugh the compilers and simulators
VHDL compiler translates the VHDL progarm into a structure that is used by
various design automation programs like simulators and silicon compilers (which
translates the design into the silicon fabricated device).
The VHDL described circuit can be tested through the simulators and hence
expensive fabrication can be avoided till the design ius tested completely
from all the angles like timing, fabrication space, etc. Simulations itself could be done at various levels like at logic circuit level, electronic circuit level and the physical
distributed parameters level reflecting the silicon fabrication.
In Computer Science, we are interested only upto logical level, although other
levels are very important. These are best left to the electrical/electronics and engineering physics people.
Notation used is a variant of famous BNF (Backus Naur Form), a metalanguage used to describe the syntax (grammer) of a programming language.
1. Entries in { } means repeated one or more number of times
2. Entries in [ ] are optional
3. | stands alternative separator (OR)
4. bold words are keywords of the language.
________________________________
Indian Institute of Technology Bombay
LEXICAL ELEMENTS
COMMENTS -- this is comments (starts with -- ) and ends with line
IDENTIFIERS are composed of letter followed by any number of underscores
or letter or digit and are names used to identify the program entities like objetc,
types etc.
identifier := letter { [underscore]letter|digit]}
Examples : my_computer, adder_bit0 , bit_10_of_A_reg
If a literal includes a point, then it represents a real number otherwise it
represents an integer. Decimal numbers are defined as follows..
Decimal_Numbers := integer[.integer][exponent]
integer := digit{[underscore]digit}
exponent := E[+] integer|E-integer
Examples: 0 12 10_000 578_2545 -- integer literals
0.5 0.001E12 10.6E-3 -- real literals
Base and exponents of real number are expressed in decimal but the value of the number is literal multiplied by the radix to the power exponent.
Radix r number examples
2#1100# binary 1100 -- the 12 in decimal
16# FF Hex FF -- 255 in decimal
2#1.111 E+2 Binary 111.1 -- 7.5 in decimal
16# D.C0 E-1 Hex real -- 13/16 + 12/256 in Hex
CHARACTERS
Single quote enclosed ASCII forms character literals of VHDL
Examples : 'A' 'c' -- characters A and c
"A" -- invalid character
STRINGS
Are given in double quotes
"COMPUTER SCIENCE AND ENGG IIT BOMBAY" -- string
BIT STRINGS
VHDL provides a convenient way of specifying literal values of arrays of type bit ( bit array)
bit_string_literal := O|X|B"digit_string" -- can have underscores
O,X,B for Octal,Hex and Bin respectively
B"110110" -- length is 6
O"354" -- length is 9
X"FF" -- length is 8
DATA TYPES AND OBJECTS
VHDL provides basic (scalar) types and means to compose composite types formed out of the basic types. The scalar types include numbers, physical quantities, and enumeration types and there are a number of standard predefined types. Composite types provided are arrays and records. Also access types( pointer types) and file types are provided by VHDL.
Type_declaration ::= Type identifier is type_definition;
type_definition ::= scalar_type_definition | composite_type_definitio
|access_type_definition | file_type_efinition
scalar_type_defintion ::= enumeration_type_efinition | integer_type_definition
|floating_type_definition |physical_type_definition
Composite_type_definition := array-type_definition | record_type_definition
Integer_type_definition := range_constraint;
range_constraint := range range
range := simple_expression direction simple_expression
direction := to | downto
Examples:
type byte _integer is range 0 to 255;
type word_int is range -32768 to 32767
type index is range 0 to 31;
There is predefined type integer whose range is -2147483647 to +2417483647
Physical Types
A numeric type used for representation of physical quantities such as mass, time, voltage, length
etc. The declaration of a physical type includes a base unit and optionally a number of secondary
units that are multiples of base unit.
Physical_type_definition := range_constraint
units
base_unit_declaration
{secondary_unit_declaration}
end units;
base_unit_declaration := identifier = physical_Literal;
physical_literal ::= [ abstract_literal] unit_name
type length is range 0 to 1 E 10
units
um; ---- micrometer
mm:= 1000 um -- milimeter
cm := 10 mm -- centimeter
m := 100 cm -- meter
in := 2.54 cm -- inch
end units;
Type capacitance is range 0 to 1 E 10
units
pf;
nf := 1000 pf;
uf := 1000 nf
mf := 1000 uf;
end units;
Examples
C1: capacitance; -- a variable of type capacitance
L1: length; -- a variable of type length;
C1:= 1000 nf; -- C1 is assigned value 1000 nf
L1 := 2 mm; -- L1 is assigned value of 2 mm
FLOATING POINT TYPES
An approximation to real numbers in a specified range. The precision of the approximation
is not defined by VHDL but must be at least 6 decimal digits. The range must include at least
-1E38 to +1E38.
Floating point_type definition := range_constraint
type signal_level is range -5.0 to + 5.0
type mass is range 0 to 1E 38;
A predefined floating point type real and has range implementation defined but includes the
range -1E38 to +1e38.
ENUMERATION TYPES
It is defined by listing the literal identifiers constituting the type elements.
enumeration_type_definition := ({enumeratuion_literal {, enumeration_literal})
enumeration_literal := identifier | character_literal
Examples
type logic_level is (unknown, low, high);
type octal_digit is (0,1,2,3,4,5,6,7);
There are a number of predefined enumeration types in VHDL. These are:
Type severity_level is (note, warning, error, failure);
type boolean is ( false, true);
type bit is ( 0, 1);
type character is ( NUL, SOH,.. ); -- list of ASCII Characters
ARRAYS
An aray is an indexed collection of elements of same type and of one or more dimensions. The
aray type could be constrained in which the bounds for indices are established when the type is
defined or unconstrained in which bound are established subsequently.
array_type_definition := unconstrained_array_definiton | constrained_array_defintion
unconstrained_array_definition := array (index_sub_type_definition {, index_subtype_definition})
of element_subtype_indication
constrained_array_defition := array index_constraint of elemet_subtype_indication}
indexed_subtype_definition := type_mark range <>
index_constraint ::= (discrete_range { , discrete_range } )
discrete_range ::= discrete_subtype_indication | range
Examples
type address is integer range 0 to 4095;
type word array ( 31 downto 0 ) of bit;
type register_file is array ( 0 to 63 ) of word;
type RAM is array ( address) of word;
vector is array ( integer range <> ) of real; --- unconstrained array type
-- range can be specified later as below
a : vector ( 1 to 20); -- a is ddeclared as variable of type
vector with elements indexed 1 to 20
Predefined unconstrained array types string and bit_vector are supported by VHDL. They are
defined as :
type string is array ( positive range <> ) of character; -- positive is subtype of integer
type bit_vector is array ( natural <> ) of bit; -- natural is subtype of integer
a, b,c : string ( 1 to 80); -- strings of 80 characters
byte : bit_vector ( 7 downto 0); -- bit array of 8 bits
Aggregates can be written to assign the values to the elements of the array or slices.
a(1 to 3 => ‘i’,’i’,’t’, others => ‘ ‘)"
RECORDS
VHDL provides basic record types which are collections of named elements of possibly
diffrrent types.
Record_type_definition ::= record
element_declaration
(element_declaration }
end record;
element_declaration ::= identifier_list : element_type_definition;
identifier_list ::= identifier {, identifier }
element_subtype_definition ::= subtype_indication
Example
type instruction is record
opcode : CPU_operation;
R : GPR;
X : GPR
Disp : integer range 0 to 4095;
end record;
SUBTYPES
Subtypes alows values to be constrined subset of some base type.
sub_type_declaration ::= subtype identifier is subtype_indication;
sub_type_indication ::= [ resolution_function_name ] type_mark [constraint ]
type_mark ::= type_name | subtype_name
constraint :: range_constraint | index_constraint
Examples
sub_type byte_integer is integer range 0 to 255 -- value constraint
subtype GPR is reg_file ( 0 to 15);
OBJECT DECLARATIONS
An object is an named item in a VHDL description which has a value of a specified type.
There are 3 basic classes of objects viz., constants , variables and signals in the VHDL
language. (Signals will be discussed later)
Constants
Constant_declaration ::= constant identifier_list : subtype_indication [ := expression };
The expression given is optional (as indicated by the square brackets. The constants without
initializations are called as deferred constants and may only appear in package declarations.
Initial value must be given in the corresponding package body.
constant pi : real := 3.14159;
cinstant delay : Time := 4 ns;
constant Max : natural;
Variables
variable identifier_list : subtype_indication [:= expression ];
The expression if present is evaluated and the value is assigned as the initial value of the variable.
On the other hand if the expression is missing, the default value is assigned. the default value is
the first value in the enumeration list of the values of the type. For a variable of the composite
type default value is the default values for each element based on the element types.
variable index is natural range 0 to 31 := 0;
Alias Declaration.
Used to give another name to the variable or to a part of it.
alias_declaration ::= alias identifier : subtype_indication is name;
variable instruction : bit_vector (31 to 0);
alias opcode : bit_vector(7 downto 0) is instruction (31 downto 24);
Attributes
Types and the objects declared in VHDL can have aditional information called attributes
associated with them. There are a number of predefined attributes to various tyope and
objecxts. Attributes are referred by putting double quote after the object followed by the attribute
identifier.
Atributes of a scalar type T
T"left -- evaluates to the left bound of T
T"right -- evaluatyes to the right bound of T
T"low -- lowest value of T
T"high -- highest value in T
For ascending range T"left is same as T"low and T"high is same is T"right. For descending
range T"left I = T’high and T"right = T"low.
For any discrete or physical type or subtype T with X as a member of T, the following are predefined.
T"pos(X) -- position of X in T
T"val (N) -- value at position N
T"leftof(X) -- value that one position left of X
T"rightof(X) -- valur that is one position right of X
T"pred(X) -- value that is predecessor of X
T"succ(X) -- value that is successor of X
Examples
Type T is integer range 0 to 31
T"pos(4) gives 3, T"succ(5) gives 6.
T"leftof(8) gives 7.
Attributes of Aray types
For any array A and N (a number between 1 and number of dimensions of A, the following
attributes are defined.
A’left(n) -- left bound of the n th dimensions’s index of the array A.
A’right(n) -- right bound of the n th dimension’s index of the array A
A’low(n) -- lower bound of the nth dimension of A
A’high(n) -- upper bound of the nth dimension
A’range(n) -- range of nth dimension
A’reverse_range (n) -- reverse range of nth dimension
A’length(n) -- length of the index range of nth dimension
EXPRESSIONS
VHDL expressions are like expressions in any other programming language . An expression is
a formula that combines primaries with the operators. Operators of VHDL expressions are:
** abs not highest precedence
* / mod rem
+ - unary + and -
+ - & binary + and -
= /= < <= > .>=
and or not nand nor xor all are short cut operators except xor
(They evaluate right side expression only if expression on left does not decide the val.ue of the
expression.
SEQUENTIAL STATEMENTS
VHDL contains a number of faclities for modifying the state of the objects and controlling the flow of the execution.
variable assignments
variable_assignment_statement ::= target := expression;
target ::= name | aggregate
In the simplest case the target of the assignment is a name of a object . The value of the expression
s given to the named object. Value must evaluate to the same base type. If the target of an assignment is an aggregate then the elements listed in the assignment must be object names and the
value of the expression must be composite value of the same type as aggregate.
(Evaluation is done as follows: First the names in the aggregate are evaluated, then the expression is
evaluated and lstly the components of the expression value are assigned to the named variables. This
is effectively a parallel assignment ( suppose r is a record with two fields a and b then
a=> r.b, b => r.a ):= r will exchange the values of the fields a and b; although this is not a good
programming practice).
IF STATEMENT
If_statenment ::= if condition then
sequence_of_statements
[ elsif condition then
sequence_of_statements ]
[ else
sequence_of_statements ]
end if;
conditions are expressions resulting in boolean values. Conditions are evaluated successively until
one that yields a true value. In that case, the corresponding then clause sequence_of_statements
is executed, otherwise if the esle clause is present, the sequence of_statements is executed.
CASE STATEMENT
case_statement ::= case expression is
case_statement_alternative
{case_statement_alternative}
end case;
case_statement_alternative ::= when choices => sequence_of_statements
choices ::= choice {| choice }
choice ::= simple_expression | discrete_range | element_simple_name | others
Case expression must give value that is either a discrete type or a one dimensional array of
characters. An alternative is selected as per the value that matches the choice giiven. In case of
when the result is an array of characters, the choices may be bit strings or strings of characters.
case day of
when mon : lt:= 8.30;
when wed : lt:= 10.30;
when fri : lt := 9.30;
when others : message := "no lecture";
lt:= 0;
end case;
case opcode of
when X"05": add;
when X"01" : IOR;
when others : exception;
end case;
LOOP STATEMENT
loop_statement := [ loop_label: ] [iteration_scheme ] loop
sequence_of_statements
end loop [loop_label];
iteration_scheme ::= while condition
| for identifier in discrete_range
When the iteration scheme is ommitted, the loop executes indefinitely.
loop
do_something;
end loop;
while not baldy
loop
do_haircut;
end loop;
for I in 1 to 100 loop
a(i):= 0;
end loop;
Next Statement and Exit Statement
It terminates the execution of the current iteration and starts the next iteration. Exit statement terminates the execution of current iteration and terimnates the loop.
next_statement ::= next [ loop_label ] [ when condition ];
exit_statement ::= exit [ loop_label ] [ when condition ];
If the loop label is ommitted the statement applies to the innermost enclosing loop, otherwise it applies to the named loop. If the when clause is present and the condition is false, the execution continues normally, otherwise termination effect takes place (condition true effect).
for I in 1 to max loop
exit when a[i] = 0;
end;
Loop1 : loop
loop2 : loop
next loop1 when a= 0;
end loop2;
end loop1;
NULL STATEMENT
if a[i] = 0 then null else a[i]:= 2; end if
Null statement does no operation. It may be useful in some cases as shown above.
ASSERTIONS
Assertions are useful for program correctness. VHDL provides an assert statement.
assert_statement ::= assert conditon [ report expression ]
[ severity expression ];
If the report clause is present, result of the expression must be string. The string is used as a message
that will be reported if the condition is false. If it is ommitted, the default message is "Assertion violation ". If the severity clause is present the expression must result into a value of type severity_level. It it is ommited, the default is error. A simulator may terminate the execution if
the severity violation occurs and the severity value is greater than some threshold value(implementation defpendent). Usually the threshold may be under the user control.
SUBPROGRAMS AND PACKAGES
VHDL provide a subprogram facility in the form of proceduires and functions. VHDL also prvides a
package facility to collect declarartions and objects into modular units. pacakges provides a
measure of data abstraction and data hiding whcih is usefull as object oriented programming style.
(Implementation available does not support packages)
Procedures and Functions
subprogram_declarartion ::= procedure subprogram_ identifier [ ( formal_parameters_list ) ]
| function subprogram_identifier_identifier
[ formal_parameter_list)] Return type_mark
formal_parameter_list ::= interface_element [; interface_element ]
interface_element ::= [ constant ] identifier_list :[ in subtype_indication [ := static_expression
| [ variable ] identifier_list : [mode ] subtype_indication [:= static_expression ]
mode ::= in | out | inout
Examples of procedure declarartions
procedure count ( variable reg : out word_32; constant increment_size : in integer := 1 );
procedure reset;
Examples of the subprogram calls
count ( index_reg, offfset-2);
count (increment_size => offset -2, reg => index_reg);
count ( reg => program_counter); --- increment is taken as 1 by default definition
Function mat_mul ( a,b : in Matrix; variable c: out Matrix ) return matrix;
Subprogram Body
Subprogram bodies are defined with the following syntax..As can be seen, its is program unit
that could have all its declrations including subprograms.
Subprogram _body ::= subprogram_specification is
{ subprogram_declarative_item }
begin
{ sequential statement }
end [subprogram_identifier ] ;
subprogram_declarative_item ::= subprogram_declaration
| subprogram_body
| type_declration
| subtype_declrartion
| constant_declration
| variable_declration
| alias_declration
Names that are declared in the subprogram are not visible outside the body of the subprogram.
When the subprogram is called, the statements in its body are executed until the end of the statement list
is encountered or a Return statement is executed.. The syntax for the Return statement is as follows.
RETURN STATEMENT
return_statement ::= return [ exotession ];
The return statement should not have expression if it is used in the procedure body. In a function
body , at least one return statement is a must and it must have an expression. Moreover function must
complete its execution with the return statement and the value returned by thefunction is the value of
the expression whiose type must be the type indicated in the function declaration.
Examples
Procedure exchange (x,y: inout integer); -- exchanges the values of x and y
variable temp: integer;
begin
temp:= x;
x::= y;
y := temp;
end;
----- calling program isegment s given below
variable
a,b,c: integer;
exchange (a,b);
Function MATADD (x,y : in MAT) return MAT is
variable z : mat;
begin
for I in 1 to 10
loop
for j in 1 to 10
loop
z(i,j) := x(i,j) + y (i,j);
end loop;
end loop
return (z);
end;
OverLoading
Overloading is the term used for indicating the use of the same name/s in the same scope of
a program. In VHDL overloading of subprograms is allowed provided their distinction could
be made while calling by means like parameters and thier types, sequence of parameters,
number of parameters and son. At least one distinctive feature must exist while calling
to resolve the ambiguity.
Examples of overloading subprogarms
functionn add (x,y: in integer; z: inout integer) return integer;
procedure add (x,y : in string ; z: inout string) return string;
PACKAGES
A package is a collection of types, constants, subprograms and possibly other things, usually intended to implement some service (in Programming language terminlogy, it implements abstract data type
providing basic support for object oriented programming paradigm). Through this programmer
can hide the details about the object and only program interface could be made visible. For example
constant values, type details, subprogram bodies may be hidden. All the accesses to the object must be
through the subprograms.
Package_declaration ::= package package_identifier is
{ type_declaration
| subtype_declartion
| constant_declaration
| alias_declaration
| use_clause
| subprogarm_declaration
}
end [package_identifier;
Examples
pacake screen is
type row is array(1 to 1024) of byte;
type display is array(1 to 1000) of rows;
function Vdsp (a: in display) return boolean ;
procedure copy_screen(a : out screen);
end screen;
Package declaration provides an interface to the user of a package. The objects declared in the
package can be used by prefixing their names with package name. The package bodies defines the
functionality to the objects.
Package body package_identifier is
{
subprogarm_declaration
| subprogram_body
| subprogram_body
| type_declaration
| subtype_declaration
| constant_declarion
| alias_declaration
| use_clause
end package_identifier;
package body screen is
constant display_mem_address : address := X"FFF0000"
constant no_of_rows : 768;
constant no_of_columns : 1024;
Function Vdisp (a: in screen ) return boolean is
begin
--------------- statements
end
Vdisp;
procedure copy_screen ( a: out screen) is
begin
for I:= 1 to no_of_rows loop
for j:= 1 to no_of_columns
loop
a[i,j]:= Mem(display_mem_address)
end loop;
end loop;
USE CLAUSE
The names declared in the package could be used by qualifying the names with the name of the package.( prefixing the name of the package followed by "." ). Use clause allows the use of names
listed in the use clause without qualifying them.
Use row, Vdisp -- allows the use of rows and screen identifiers with prefixing them.
If use clause is not present, then the same can be accessed as
screen.rows screen. Vdisp -- qualified names
HARDWARE STRUCTURE DESCRIPTION
THROUGH VHDL
A digital system is usually designed as hierarchical collection of circuit modules that are interconnected through the signal lines external to the modules. Each module thus has a port consituting of these signal lines, through which it interacts with the outside world. VHDL provides the structuarl description via varipus language constructs available for this
purpose.
The modules of a circuit are called entities in VHDL and can be declared using entity
declarartion .
Entity_declaration ::= entity entity_identifier is
entity_header
entity_declarative_part
[ begin
entity_statement_part
]
end [ entity_identifier ] ;
Entity_header ::= [ generic_clause ]
[ formal_port_clause ]
generic_clause ::= generic (generic_list);
generic_list ::= generic_interface_list
port_clause ::= port (port_list)
port_list ::= port_interface_list
entity-declarative_part ::= [ entity_declarative_item ]
Examples
Entity CPU is
generic (max_clock_freq : frequency := 20 Mhz );
port ( clock : in bit;
address : out integer;
data : inout word;
control : out CPU_control_lines;
ready : in bit );
end CPU;
Entity RAM is
generic ( word_length, no_of _addr_bits : natural );
port ( Enable : in bit;
RW : in bit;
data : inout Bit_vector (word_length-1 downto 0);
address: in bit_vector (no_of_addr_bits -1 downto 0)
);
end RAM;
Entity 2-input_nand_gate is -- two input nand gate templates
port (a,b: in bit ; c: out bit);
end 2_input_nand_gate;
Entity nand_gate is -- n input nand gate template
generic ( n : 1 to 10 := 2 ); -- actual nand gate can be declared with n inputs
port ( a: bit_vector (1 to 10); c: out bit ); -- defined later when instantiated.
end nand_gate;
ARCHITECTURE DECLARATIONS
Once an entity is defined witgh its interface, implementations of the entity can be defined. We could
define one or more implementations of the same entity and we could associate one of the implementation with the entity. This could be chnged later if required by changing the association.
This is achieved by architecture declaration for the entity. We can define number of architecures
for an entity and associate one of them with it. For example architecture body can implement
the behaviour of the entity using programming constructs defined or a body could have implementation of the entity thriough the subsystems that are interconnected. Architecture declarations is done with following syntax.
architecture architecture_identifier of entity_identifier is
architecture_declarative_part
begin
architecture_statement_part;
end [ architecture_identifier ] ;
architecture_declrative_part ::= { block_declarative_item }
architecture_statement_part ::= { concurrent_statement }
block_declarative_item ::= subprogram_declaration
| type_declaration
| sub_type_declaration
| constant_declaration
| signal_declaration
| alias_declaration
| component_declaration
| configuration_specification
| use clause;
Concurrent_statement ::= block_statement | component_instantiation_statement
signal_declaration ::= signal identifier_list : subtype_indication [ register | Bus ] [:= expression] ;
block_statement ::= block_label : block [ (guard_expression } ]
block_header
block_declarative_part
begin
block_sytatement_part
end block [ block_label ];
block_header ::= [generic_clause [generic_map_aspect ; ] ] [port_clause [ port_map_aspect; ] ]
generic_map_aspect ::= generic map (generic_association_list )
block_declarative_part ::= { block_declarative_item }
block_statement_part ::= { concurrent_statement }
Component Declarations ::=
component_declaration ::= compoenet identifier [ local_geberic_clause ][ local_port_clause ] end component;
Examples
component nand
generic (delay : time := 1ns )
port (a,b,c in bit ; d : out bit );
end component;
Component RAM
generic ((width, depth : number );
port (cs ,rw: in bit; addr : in bit_vector( depth - 1 downto 0 );
data : in out bit_vector ( width - 1 downto 0) ;
end component;
Component_instantiation
Component_instantiation_statement ::= instantiation_label : [generic_map_aspect ] [ port_map_aspect];
Example
g1: Ngate port map (a,b,c);
Par_RAM: RAM generic map (depth => 10, width => 8);
port map (cs => ram_select, data => data_in , rw=> read, addr => a(9 downto 0) );
BEHAVIORAL DESCRIPTION THROUGH VHDL
Signal Assignment
signal assignment schedules one or more transactions to a signal or port.
Signal_assignment ::= target := [transport ] waveform;
target ::= name | aggregate -- signal or agggregate of signals
waveform ::= waveform_element |{, waveform_elelemnt }
waveform_elelemnt ::= value_expression [ after time_expression ] | null [ after time_expression ]
If time_expression is ommitted it defaults to 0. This means that transaction will be scheduled for the
same time as the assignment is executed (during the next simulation cycle).
Examples
s := ‘0’ after 10 ns;
Process Statement
Primary Unit for describing behaviour in VHDL is a process. A process is a sequential body of code whuch can be
activated in response to changes in the state.When more than one process is activated at the same time they
execute concurrently.
Process_statement ::= process [ (sensitivity_list) ]
process_declrative_part
begin
process_statement_part
end process;
process_declrative_part ::= { process_declrative_item }
process_declrative_item ::= subprogram_declration
| type_declrartion
| subtype_declration
| constant_declration
| variable_declration
| alias_declration
| use_clause
Process_statement_part ::= {sequential_statement }
sequential_statement ::= wait_statement
| assertion_statement
| signal_assignment_statement
| variable_assignment_statement_statement
| procedure_call_statement
| if_statement
| case_statement
| loop_statement
| next_statement
| exit_statement
| return_statement
| null_statement
Process statement is a concurrent statement and can be sued in an architecture body or block. The declarations define
items which can be used locally within a process. Note that variables may be defined and used to
store the state in a model. A process is started initially during the initialisation phase of simulation. It executes all
of the sequential statements and then repeats starting from the first statement . A process may be suspended itrself by
executing a wait statement.
Wait Statement
wait_statement ::= [ sensitivity_clause ] [ condition_clause ] [ time_out_clause ] ;
sensitivity_clause ::= on sensitivity_list
sensitivity_list ::= signal_name {, signa_name }
condition_clause ::= until condition
timeout_clause ::= for time_expression
If a sensitivity list is included at the header of a process then it is assumed to have an implicit wait statement
at the end of its statement part, with the list of variables given in the header as a sensitivity list. In such cases
process may not have any explicit wait statement.
Conditional Signal Assignment Statement
Conditional_signal_assignment ::= target <= [guarded ] [ transport ] waveform when condition else waveform;
Word transport when used, the process use transport delay.
For example
s:= waveform_1 when condition_1 else
waveform_2 when condition_2 else
….
Waveform_n;
The equivalent process is
process
if condition_1 then s:= waveform-1 ;
elsif condition_2 then s:= waveform_2;
elsif …
else s:= waveform_n
wait [ sensitivit_clause];
end process;
Reset <= ‘1’ , ‘0’ afte 10 ns when short_pulse_required else ‘1’,’0’ after 50 ns;
Selected Signal Assignment
selected_signal_assignment ::= with expression select
target <= [guarded] [transport] {waveform when choice {|choice } ,}
waveform when choice { | choice }